Add tagged types for BME280 sensors

to allow a user to declare several sensor objects and
process them in a uniform way.
This commit is contained in:
Maxim Reznik 2023-12-16 12:59:42 +02:00
parent 87bb2514f5
commit 49eb4e10e1
16 changed files with 1341 additions and 323 deletions

View File

@ -0,0 +1,93 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 generic package contains shared code independent of the sensor
-- connection method. Following the Singleton pattern, it is convenient
-- when using only one sensor is required.
with HAL.Time;
generic
with procedure Read
(Data : out HAL.UInt8_Array;
Success : out Boolean);
-- Read the values from the BME280 chip registers into Data.
-- Each element in the Data corresponds to a specific register address
-- in the chip, so Data'Range determines the range of registers to read.
-- The value read from register X will be stored in Data(X), so
-- Data'Range should be of the Register_Address subtype.
with procedure Write
(Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
-- Write the value to the BME280 chip register with given Address.
package BME280.Generic_Sensor is
function Check_Chip_Id (Expect : HAL.UInt8 := 16#60#) return Boolean;
-- Read the chip ID and check that it matches
procedure Reset
(Timer : not null HAL.Time.Any_Delays;
Success : out Boolean);
-- Issue a soft reset and wait until the chip is ready.
procedure Configure
(Standby : Standby_Duration := 1000.0;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean);
-- Configure the sensor to use IRR filtering and/or SPI 3-wire mode
procedure Start
(Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean);
-- Change sensor mode. Mainly used to start one measurement or enable
-- perpetual cycling of measurements and inactive periods.
function Measuring return Boolean;
-- Check if a measurement is in progress
procedure Read_Measurement
(Value : out Measurement;
Success : out Boolean);
-- Read the raw measurement values from the sensor
procedure Read_Calibration
(Value : out Calibration_Constants;
Success : out Boolean);
-- Read the calibration constants from the sensor
end BME280.Generic_Sensor;

View File

@ -29,10 +29,15 @@
-- --
------------------------------------------------------------------------------
-- This package provides an easy way to setup BME280 connected via I2C.
-- This package offers a straightforward method for setting up the BME280
-- when connected via I2C, especially useful when the use of only one sensor
-- is required. If you need multiple sensors, it is preferable to use the
-- BME280.I2C_Sensors package, which provides the appropriate tagged type.
with HAL.I2C;
with BME280.Generic_Sensor;
generic
I2C_Port : not null HAL.I2C.Any_I2C_Port;
I2C_Address : HAL.UInt7 := 16#76#; -- The BME280 7-bit I2C address
@ -44,9 +49,10 @@ package BME280.I2C is
-- Read registers starting from Data'First
procedure Write
(Data : HAL.UInt8_Array;
(Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
-- Write registers starting from Data'First
-- Write the value to the BME280 chip register with given Address.
package Sensor is new Generic_Sensor (Read, Write);

View File

@ -0,0 +1,115 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 package provides a type representing the BME280 connected via the I2C
-- interface.
with HAL.I2C;
with HAL.Time;
with BME280.Sensors;
package BME280.I2C_Sensors is
Default_Address : constant HAL.UInt7 := 16#76#;
-- The typical BME280 7-bit I2C address
type BME280_I2C_Sensor
(I2C_Port : not null HAL.I2C.Any_I2C_Port;
I2C_Address : HAL.UInt7) is limited new BME280.Sensors.Sensor with
record
Calibration : Calibration_Constants;
end record;
overriding function Check_Chip_Id
(Self : BME280_I2C_Sensor;
Expect : HAL.UInt8 := 16#60#) return Boolean;
-- Read the chip ID and check that it matches
overriding procedure Reset
(Self : BME280_I2C_Sensor;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean);
-- Issue a soft reset and wait until the chip is ready.
overriding procedure Configure
(Self : BME280_I2C_Sensor;
Standby : Standby_Duration := 0.5;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean);
-- Configure the sensor to use IRR filtering and/or SPI 3-wire mode
overriding procedure Start
(Self : BME280_I2C_Sensor;
Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean);
-- Change sensor mode. Mainly used to start one measurement or enable
-- perpetual cycling of measurements and inactive periods.
overriding function Measuring (Self : BME280_I2C_Sensor) return Boolean;
-- Check if a measurement is in progress
overriding procedure Read_Measurement
(Self : BME280_I2C_Sensor;
Value : out Measurement;
Success : out Boolean);
-- Read the raw measurement values from the sensor
overriding function Temperature
(Self : BME280_I2C_Sensor;
Value : Measurement) return Deci_Celsius is
(Temperature (Value, Self.Calibration));
-- Get the temperature from raw values in 0.1 Celsius
overriding function Humidity
(Self : BME280_I2C_Sensor;
Value : Measurement;
Temperature : Deci_Celsius) return Relative_Humidity is
(Humidity (Value, Temperature, Self.Calibration));
-- Get the humidity from raw values
overriding function Pressure
(Self : BME280_I2C_Sensor;
Value : Measurement;
Temperature : Deci_Celsius) return Pressure_Pa is
(Pressure (Value, Temperature, Self.Calibration));
-- Get the pressure from raw values
overriding procedure Read_Calibration
(Self : in out BME280_I2C_Sensor;
Success : out Boolean);
-- Read the calibration constants from the sensor
end BME280.I2C_Sensors;

View File

@ -0,0 +1,98 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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.Time;
package BME280.Sensors is
type Sensor is limited interface;
function Check_Chip_Id
(Self : Sensor;
Expect : HAL.UInt8 := 16#60#) return Boolean is abstract;
-- Read the chip ID and check that it matches
procedure Reset
(Self : Sensor;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean) is abstract;
-- Issue a soft reset and wait until the chip is ready.
procedure Configure
(Self : Sensor;
Standby : Standby_Duration := 0.5;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean) is abstract;
-- Configure the sensor to use IRR filtering and/or SPI 3-wire mode
procedure Start
(Self : Sensor;
Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean) is abstract;
-- Change sensor mode. Mainly used to start one measurement or enable
-- perpetual cycling of measurements and inactive periods.
function Measuring (Self : Sensor) return Boolean is abstract;
-- Check if a measurement is in progress
procedure Read_Measurement
(Self : Sensor;
Value : out Measurement;
Success : out Boolean) is abstract;
-- Read the raw measurement values from the sensor
function Temperature
(Self : Sensor;
Value : Measurement) return Deci_Celsius is abstract;
-- Get the temperature from raw values in 0.1 Celsius
function Humidity
(Self : Sensor;
Value : Measurement;
Temperature : Deci_Celsius) return Relative_Humidity is abstract;
-- Get the humidity from raw values
function Pressure
(Self : Sensor;
Value : Measurement;
Temperature : Deci_Celsius) return Pressure_Pa is abstract;
-- Get the pressure from raw values
procedure Read_Calibration
(Self : in out Sensor;
Success : out Boolean) is abstract;
-- Read the calibration constants from the sensor
end BME280.Sensors;

View File

@ -29,11 +29,16 @@
-- --
------------------------------------------------------------------------------
-- This package provides an easy way to setup BME280 connected via SPI.
-- This package offers a straightforward method for setting up the BME280
-- when connected via SPI, especially useful when the use of only one sensor
-- is required. If you need multiple sensors, it is preferable to use the
-- BME280.SPI_Sensors package, which provides the appropriate tagged type.
with HAL.GPIO;
with HAL.SPI;
with BME280.Generic_Sensor;
generic
SPI_Port : not null HAL.SPI.Any_SPI_Port;
SPI_CS : not null HAL.GPIO.Any_GPIO_Point;
@ -45,9 +50,10 @@ package BME280.SPI is
-- Read registers starting from Data'First
procedure Write
(Data : HAL.UInt8_Array;
(Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
-- Write registers starting from Data'First
-- Write the value to the BME280 chip register with given Address.
package Sensor is new Generic_Sensor (Read, Write);

View File

@ -0,0 +1,114 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 package provides a type representing the BME280 connected via the SPI
-- interface.
with HAL.GPIO;
with HAL.SPI;
with HAL.Time;
with BME280.Sensors;
package BME280.SPI_Sensors is
type BME280_SPI_Sensor
(SPI_Port : not null HAL.SPI.Any_SPI_Port;
SPI_CS : not null HAL.GPIO.Any_GPIO_Point)
is limited new BME280.Sensors.Sensor with
record
Calibration : Calibration_Constants;
end record;
overriding function Check_Chip_Id
(Self : BME280_SPI_Sensor;
Expect : HAL.UInt8 := 16#60#) return Boolean;
-- Read the chip ID and check that it matches
overriding procedure Reset
(Self : BME280_SPI_Sensor;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean);
-- Issue a soft reset and wait until the chip is ready.
overriding procedure Configure
(Self : BME280_SPI_Sensor;
Standby : Standby_Duration := 0.5;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean);
-- Configure the sensor to use IRR filtering and/or SPI 3-wire mode
overriding procedure Start
(Self : BME280_SPI_Sensor;
Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean);
-- Change sensor mode. Mainly used to start one measurement or enable
-- perpetual cycling of measurements and inactive periods.
overriding function Measuring (Self : BME280_SPI_Sensor) return Boolean;
-- Check if a measurement is in progress
overriding procedure Read_Measurement
(Self : BME280_SPI_Sensor;
Value : out Measurement;
Success : out Boolean);
-- Read the raw measurement values from the sensor
overriding function Temperature
(Self : BME280_SPI_Sensor;
Value : Measurement) return Deci_Celsius is
(Temperature (Value, Self.Calibration));
-- Get the temperature from raw values in 0.1 Celsius
overriding function Humidity
(Self : BME280_SPI_Sensor;
Value : Measurement;
Temperature : Deci_Celsius) return Relative_Humidity is
(Humidity (Value, Temperature, Self.Calibration));
-- Get the humidity from raw values
overriding function Pressure
(Self : BME280_SPI_Sensor;
Value : Measurement;
Temperature : Deci_Celsius) return Pressure_Pa is
(Pressure (Value, Temperature, Self.Calibration));
-- Get the pressure from raw values
overriding procedure Read_Calibration
(Self : in out BME280_SPI_Sensor;
Success : out Boolean);
-- Read the calibration constants from the sensor
end BME280.SPI_Sensors;

View File

@ -31,237 +31,12 @@
pragma Ada_2022;
with Ada.Unchecked_Conversion;
package body BME280 is
OS_Map : constant array (Oversampling_Kind) of Natural :=
[Skip => 0, X1 => 1, X2 => 2, X4 => 4, X8 => 8, X16 => 16];
-- Map Oversamping_Kind to the integer value
package body Generic_Sensor is
-------------------
-- Check_Chip_Id --
-------------------
function Check_Chip_Id (Expect : HAL.UInt8 := 16#60#) return Boolean is
use type HAL.UInt8_Array;
Ok : Boolean;
Data : HAL.UInt8_Array (16#D0# .. 16#D0#);
begin
Read (Data, Ok);
return Ok and Data = [Expect];
end Check_Chip_Id;
---------------
-- Configure --
---------------
procedure Configure
(Standby : Standby_Duration := 1000.0;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean)
is
use type HAL.UInt8;
Data : HAL.UInt8;
begin
if Standby = 0.5 then
Data := 0;
elsif Standby = 20.0 then
Data := 7;
elsif Standby = 10.0 then
Data := 6;
else
Data := 5;
declare
Value : Standby_Duration := 1000.0;
begin
while Value > Standby loop
Value := Value / 2;
Data := Data - 1;
end loop;
end;
end if;
Data := Data * 8 + IRR_Filter_Kind'Pos (Filter);
Data := Data * 4 + Boolean'Pos (SPI_3_Wire);
Write ([16#F5# => Data], Success);
end Configure;
---------------
-- Measuring --
---------------
function Measuring return Boolean is
use type HAL.UInt8;
Ok : Boolean;
Data : HAL.UInt8_Array (16#F3# .. 16#F3#);
begin
Read (Data, Ok);
return Ok and (Data (Data'First) and 8) /= 0;
end Measuring;
----------------------
-- Read_Calibration --
----------------------
procedure Read_Calibration
(Value : out Calibration_Constants;
Success : out Boolean)
is
use Interfaces;
function Cast is new Ada.Unchecked_Conversion
(Unsigned_16, Integer_16);
function To_Unsigned (LSB, MSB : HAL.UInt8) return Unsigned_16 is
(Unsigned_16 (LSB) + Shift_Left (Unsigned_16 (MSB), 8));
function To_Integer (LSB, MSB : HAL.UInt8) return Integer_16 is
(Cast (To_Unsigned (LSB, MSB)));
begin
declare
Data : HAL.UInt8_Array (16#88# .. 16#A1#);
begin
Read (Data, Success);
if not Success then
return;
end if;
Value.T1 := To_Unsigned (Data (16#88#), Data (16#89#));
Value.T2 := To_Integer (Data (16#8A#), Data (16#8B#));
Value.T3 := To_Integer (Data (16#8C#), Data (16#8D#));
Value.P1 := To_Unsigned (Data (16#8E#), Data (16#8F#));
Value.P2 := To_Integer (Data (16#90#), Data (16#91#));
Value.P3 := To_Integer (Data (16#92#), Data (16#93#));
Value.P4 := To_Integer (Data (16#94#), Data (16#95#));
Value.P5 := To_Integer (Data (16#96#), Data (16#97#));
Value.P6 := To_Integer (Data (16#98#), Data (16#99#));
Value.P7 := To_Integer (Data (16#9A#), Data (16#9B#));
Value.P8 := To_Integer (Data (16#9C#), Data (16#9D#));
Value.P9 := To_Integer (Data (16#9E#), Data (16#9F#));
Value.H1 := Unsigned_8 (Data (16#A1#));
end;
declare
use type HAL.UInt8;
Data : HAL.UInt8_Array (16#E1# .. 16#E7#);
begin
Read (Data, Success);
if not Success then
return;
end if;
Value.H2 := To_Integer (Data (16#E1#), Data (16#E2#));
Value.H3 := Unsigned_8 (Data (16#E3#));
Value.H4 := Shift_Left (Unsigned_16 (Data (16#E4#)), 4) +
Unsigned_16 (Data (16#E5#) and 16#0F#);
Value.H5 := Shift_Right (Unsigned_16 (Data (16#E5#)), 4) +
Shift_Left (Unsigned_16 (Data (16#E6#)), 4);
Value.H6 := Unsigned_8 (Data (16#E7#));
end;
end Read_Calibration;
----------------------
-- Read_Measurement --
----------------------
procedure Read_Measurement
(Value : out Measurement;
Success : out Boolean)
is
use Interfaces;
Data : HAL.UInt8_Array (16#F7# .. 16#FE#);
begin
Read (Data, Success);
if Success then
Value.Raw_Press := HAL.UInt20
(Shift_Left (Unsigned_32 (Data (16#F7#)), 12)
+ Shift_Left (Unsigned_32 (Data (16#F8#)), 4)
+ Shift_Right (Unsigned_32 (Data (16#F9#)), 4));
Value.Raw_Temp := HAL.UInt20
(Shift_Left (Unsigned_32 (Data (16#FA#)), 12)
+ Shift_Left (Unsigned_32 (Data (16#FB#)), 4)
+ Shift_Right (Unsigned_32 (Data (16#FC#)), 4));
Value.Raw_Hum := HAL.UInt16
(Shift_Left (Unsigned_16 (Data (16#FD#)), 8)
+ Unsigned_16 (Data (16#FE#)));
end if;
end Read_Measurement;
-----------
-- Reset --
-----------
procedure Reset
(Timer : not null HAL.Time.Any_Delays;
Success : out Boolean)
is
use type HAL.UInt8;
Data : HAL.UInt8_Array (16#F3# .. 16#F3#);
begin
Write ([16#E0# => 16#B6#], Success);
if not Success then
return;
end if;
for J in 1 .. 3 loop
Timer.Delay_Milliseconds (2);
Read (Data, Success);
if Success and then (Data (Data'First) and 1) = 0 then
return;
end if;
end loop;
Success := False;
end Reset;
-----------
-- Start --
-----------
procedure Start
(Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean)
is
use type HAL.UInt8;
Data : HAL.UInt8;
begin
Write ([16#F2# => Oversampling_Kind'Pos (Humidity)], Success);
if Success then
Data := Oversampling_Kind'Pos (Temperature);
Data := Data * 8 + Oversampling_Kind'Pos (Pressure);
Data := Data * 4 + Sensor_Mode'Enum_Rep (Mode);
Write ([16#F4# => Data], Success);
end if;
end Start;
end Generic_Sensor;
--------------
-- Humidity --
--------------

View File

@ -31,7 +31,6 @@
with Interfaces;
with HAL;
with HAL.Time;
package BME280 is
pragma Preelaborate;
@ -120,66 +119,6 @@ package BME280 is
Temperature : Oversampling_Kind := X1) return Positive;
-- Typical measurement time in microseconds
generic
with procedure Read
(Data : out HAL.UInt8_Array;
Success : out Boolean);
-- Read the values from the BME280 chip registers into Data.
-- Each element in the Data corresponds to a specific register address
-- in the chip, so Data'Range determines the range of registers to read.
-- The value read from register X will be stored in Data(X), so
-- Data'Range should be of the Register_Address subtype.
with procedure Write
(Data : HAL.UInt8_Array;
Success : out Boolean);
-- Write the values from Data to the BME280 chip registers.
-- Each element in the Data corresponds to a specific register address
-- in the chip, so Data'Range determines the range of registers to
-- write. The value for register X will be read from Data(X), so
-- Data'Range should be of the Register_Address subtype.
package Generic_Sensor is
function Check_Chip_Id (Expect : HAL.UInt8 := 16#60#) return Boolean;
-- Read the chip ID and check that it matches
procedure Reset
(Timer : not null HAL.Time.Any_Delays;
Success : out Boolean);
-- Issue a soft reset and wait until the chip is ready.
procedure Configure
(Standby : Standby_Duration := 1000.0;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean);
-- Configure the sensor to use IRR filtering and/or SPI 3-wire mode
procedure Start
(Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean);
-- Change sensor mode. Mainly used to start one measurement or enable
-- perpetual cycling of measurements and inactive periods.
function Measuring return Boolean;
-- Check if a measurement is in progress
procedure Read_Measurement
(Value : out Measurement;
Success : out Boolean);
-- Read the raw measurement values from the sensor
procedure Read_Calibration
(Value : out Calibration_Constants;
Success : out Boolean);
-- Read the calibration constants from the sensor
end Generic_Sensor;
private
for Sensor_Mode use (Sleep => 0, Forced => 1, Normal => 3);

View File

@ -0,0 +1,156 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 BME280.Internal;
package body BME280.Generic_Sensor is
type Null_Record is null record;
Chip : constant Null_Record := (null record);
procedure Read_Sensor
(Ignore : Null_Record;
Data : out HAL.UInt8_Array;
Success : out Boolean);
procedure Write_Sensor
(Ignore : Null_Record;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
------------
-- Sensor --
------------
package Sensor is new BME280.Internal
(Null_Record, Read_Sensor, Write_Sensor);
-------------------
-- Check_Chip_Id --
-------------------
function Check_Chip_Id (Expect : HAL.UInt8 := 16#60#) return Boolean
is (Sensor.Check_Chip_Id (Chip, Expect));
---------------
-- Configure --
---------------
procedure Configure
(Standby : Standby_Duration := 1000.0;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean) is
begin
Sensor.Configure (Chip, Standby, Filter, SPI_3_Wire, Success);
end Configure;
---------------
-- Measuring --
---------------
function Measuring return Boolean is (Sensor.Measuring (Chip));
----------------------
-- Read_Calibration --
----------------------
procedure Read_Calibration
(Value : out Calibration_Constants;
Success : out Boolean) is
begin
Sensor.Read_Calibration (Chip, Value, Success);
end Read_Calibration;
----------------------
-- Read_Measurement --
----------------------
procedure Read_Measurement
(Value : out Measurement;
Success : out Boolean) is
begin
Sensor.Read_Measurement (Chip, Value, Success);
end Read_Measurement;
-----------------
-- Read_Sensor --
-----------------
procedure Read_Sensor
(Ignore : Null_Record;
Data : out HAL.UInt8_Array;
Success : out Boolean) is
begin
Read (Data, Success);
end Read_Sensor;
-----------
-- Reset --
-----------
procedure Reset
(Timer : not null HAL.Time.Any_Delays;
Success : out Boolean) is
begin
Sensor.Reset (Chip, Timer, Success);
end Reset;
-----------
-- Start --
-----------
procedure Start
(Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean) is
begin
Sensor.Start (Chip, Mode, Humidity, Pressure, Temperature, Success);
end Start;
------------------
-- Write_Sensor --
------------------
procedure Write_Sensor
(Ignore : Null_Record;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean) is
begin
Write (Address, Data, Success);
end Write_Sensor;
end BME280.Generic_Sensor;

View File

@ -59,7 +59,8 @@ package body BME280.I2C is
-----------
procedure Write
(Data : HAL.UInt8_Array;
(Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean)
is
use type HAL.I2C.I2C_Status;
@ -69,9 +70,9 @@ package body BME280.I2C is
begin
I2C_Port.Mem_Write
(Addr => 2 * HAL.UInt10 (I2C_Address),
Mem_Addr => HAL.UInt16 (Data'First),
Mem_Addr => HAL.UInt16 (Address),
Mem_Addr_Size => HAL.I2C.Memory_Size_8b,
Data => Data,
Data => (1 => Data),
Status => Status);
Success := Status = HAL.I2C.Ok;

View File

@ -0,0 +1,175 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 BME280.Internal;
package body BME280.I2C_Sensors is
procedure Read
(Self : BME280_I2C_Sensor'Class;
Data : out HAL.UInt8_Array;
Success : out Boolean);
procedure Write
(Self : BME280_I2C_Sensor'Class;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
package Sensor is
new BME280.Internal (BME280_I2C_Sensor'Class, Read, Write);
-------------------
-- Check_Chip_Id --
-------------------
overriding function Check_Chip_Id
(Self : BME280_I2C_Sensor;
Expect : HAL.UInt8 := 16#60#) return Boolean is
(Sensor.Check_Chip_Id (Self, Expect));
---------------
-- Configure --
---------------
overriding procedure Configure
(Self : BME280_I2C_Sensor;
Standby : Standby_Duration := 0.5;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean) is
begin
Sensor.Configure (Self, Standby, Filter, SPI_3_Wire, Success);
end Configure;
overriding function Measuring (Self : BME280_I2C_Sensor) return Boolean is
(Sensor.Measuring (Self));
----------
-- Read --
----------
procedure Read
(Self : BME280_I2C_Sensor'Class;
Data : out HAL.UInt8_Array;
Success : out Boolean)
is
use type HAL.I2C.I2C_Status;
use type HAL.UInt10;
Status : HAL.I2C.I2C_Status;
begin
Self.I2C_Port.Mem_Read
(Addr => 2 * HAL.UInt10 (Self.I2C_Address),
Mem_Addr => HAL.UInt16 (Data'First),
Mem_Addr_Size => HAL.I2C.Memory_Size_8b,
Data => Data,
Status => Status);
Success := Status = HAL.I2C.Ok;
end Read;
----------------------
-- Read_Measurement --
----------------------
overriding procedure Read_Measurement
(Self : BME280_I2C_Sensor;
Value : out Measurement;
Success : out Boolean) is
begin
Sensor.Read_Measurement (Self, Value, Success);
end Read_Measurement;
----------------------
-- Read_Calibration --
----------------------
overriding procedure Read_Calibration
(Self : in out BME280_I2C_Sensor;
Success : out Boolean) is
begin
Sensor.Read_Calibration (Self, Self.Calibration, Success);
end Read_Calibration;
-----------
-- Reset --
-----------
overriding procedure Reset
(Self : BME280_I2C_Sensor;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean) is
begin
Sensor.Reset (Self, Timer, Success);
end Reset;
-----------
-- Start --
-----------
overriding procedure Start
(Self : BME280_I2C_Sensor;
Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean) is
begin
Sensor.Start (Self, Mode, Humidity, Pressure, Temperature, Success);
end Start;
-----------
-- Write --
-----------
procedure Write
(Self : BME280_I2C_Sensor'Class;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean)
is
use type HAL.I2C.I2C_Status;
use type HAL.UInt10;
Status : HAL.I2C.I2C_Status;
begin
Self.I2C_Port.Mem_Write
(Addr => 2 * HAL.UInt10 (Self.I2C_Address),
Mem_Addr => HAL.UInt16 (Address),
Mem_Addr_Size => HAL.I2C.Memory_Size_8b,
Data => (1 => Data),
Status => Status);
Success := Status = HAL.I2C.Ok;
end Write;
end BME280.I2C_Sensors;

View File

@ -0,0 +1,266 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 Ada.Unchecked_Conversion;
package body BME280.Internal is
-------------------
-- Check_Chip_Id --
-------------------
function Check_Chip_Id
(Device : Device_Context;
Expect : HAL.UInt8) return Boolean
is
use type HAL.UInt8_Array;
Ok : Boolean;
Data : HAL.UInt8_Array (16#D0# .. 16#D0#);
begin
Read (Device, Data, Ok);
return Ok and Data = [Expect];
end Check_Chip_Id;
---------------
-- Configure --
---------------
procedure Configure
(Device : Device_Context;
Standby : Standby_Duration;
Filter : IRR_Filter_Kind;
SPI_3_Wire : Boolean;
Success : out Boolean)
is
use type HAL.UInt8;
Data : HAL.UInt8;
begin
if Standby = 0.5 then
Data := 0;
elsif Standby = 20.0 then
Data := 7;
elsif Standby = 10.0 then
Data := 6;
else
Data := 5;
declare
Value : Standby_Duration := 1000.0;
begin
while Value > Standby loop
Value := Value / 2;
Data := Data - 1;
end loop;
end;
end if;
Data := Data * 8 + IRR_Filter_Kind'Pos (Filter);
Data := Data * 4 + Boolean'Pos (SPI_3_Wire);
Write (Device, 16#F5#, Data, Success);
end Configure;
---------------
-- Measuring --
---------------
function Measuring (Device : Device_Context) return Boolean is
use type HAL.UInt8;
Ok : Boolean;
Data : HAL.UInt8_Array (16#F3# .. 16#F3#);
begin
Read (Device, Data, Ok);
return Ok and (Data (Data'First) and 8) /= 0;
end Measuring;
----------------------
-- Read_Calibration --
----------------------
procedure Read_Calibration
(Device : Device_Context;
Value : out Calibration_Constants;
Success : out Boolean)
is
use Interfaces;
function Cast is new Ada.Unchecked_Conversion
(Unsigned_16, Integer_16);
function To_Unsigned (LSB, MSB : HAL.UInt8) return Unsigned_16 is
(Unsigned_16 (LSB) + Shift_Left (Unsigned_16 (MSB), 8));
function To_Integer (LSB, MSB : HAL.UInt8) return Integer_16 is
(Cast (To_Unsigned (LSB, MSB)));
begin
declare
Data : HAL.UInt8_Array (16#88# .. 16#A1#);
begin
Read (Device, Data, Success);
if not Success then
return;
end if;
Value.T1 := To_Unsigned (Data (16#88#), Data (16#89#));
Value.T2 := To_Integer (Data (16#8A#), Data (16#8B#));
Value.T3 := To_Integer (Data (16#8C#), Data (16#8D#));
Value.P1 := To_Unsigned (Data (16#8E#), Data (16#8F#));
Value.P2 := To_Integer (Data (16#90#), Data (16#91#));
Value.P3 := To_Integer (Data (16#92#), Data (16#93#));
Value.P4 := To_Integer (Data (16#94#), Data (16#95#));
Value.P5 := To_Integer (Data (16#96#), Data (16#97#));
Value.P6 := To_Integer (Data (16#98#), Data (16#99#));
Value.P7 := To_Integer (Data (16#9A#), Data (16#9B#));
Value.P8 := To_Integer (Data (16#9C#), Data (16#9D#));
Value.P9 := To_Integer (Data (16#9E#), Data (16#9F#));
Value.H1 := Unsigned_8 (Data (16#A1#));
end;
declare
use type HAL.UInt8;
Data : HAL.UInt8_Array (16#E1# .. 16#E7#);
begin
Read (Device, Data, Success);
if not Success then
return;
end if;
Value.H2 := To_Integer (Data (16#E1#), Data (16#E2#));
Value.H3 := Unsigned_8 (Data (16#E3#));
Value.H4 := Shift_Left (Unsigned_16 (Data (16#E4#)), 4) +
Unsigned_16 (Data (16#E5#) and 16#0F#);
Value.H5 := Shift_Right (Unsigned_16 (Data (16#E5#)), 4) +
Shift_Left (Unsigned_16 (Data (16#E6#)), 4);
Value.H6 := Unsigned_8 (Data (16#E7#));
end;
end Read_Calibration;
----------------------
-- Read_Measurement --
----------------------
procedure Read_Measurement
(Device : Device_Context;
Value : out Measurement;
Success : out Boolean)
is
use Interfaces;
Data : HAL.UInt8_Array (16#F7# .. 16#FE#);
begin
Read (Device, Data, Success);
if Success then
Value.Raw_Press := HAL.UInt20
(Shift_Left (Unsigned_32 (Data (16#F7#)), 12)
+ Shift_Left (Unsigned_32 (Data (16#F8#)), 4)
+ Shift_Right (Unsigned_32 (Data (16#F9#)), 4));
Value.Raw_Temp := HAL.UInt20
(Shift_Left (Unsigned_32 (Data (16#FA#)), 12)
+ Shift_Left (Unsigned_32 (Data (16#FB#)), 4)
+ Shift_Right (Unsigned_32 (Data (16#FC#)), 4));
Value.Raw_Hum := HAL.UInt16
(Shift_Left (Unsigned_16 (Data (16#FD#)), 8)
+ Unsigned_16 (Data (16#FE#)));
end if;
end Read_Measurement;
-----------
-- Reset --
-----------
procedure Reset
(Device : Device_Context;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean)
is
use type HAL.UInt8;
Data : HAL.UInt8_Array (16#F3# .. 16#F3#);
begin
Write (Device, 16#E0#, 16#B6#, Success);
if not Success then
return;
end if;
for J in 1 .. 3 loop
Timer.Delay_Milliseconds (2);
Read (Device, Data, Success);
if Success and then (Data (Data'First) and 1) = 0 then
return;
end if;
end loop;
Success := False;
end Reset;
-----------
-- Start --
-----------
procedure Start
(Device : Device_Context;
Mode : Sensor_Mode;
Humidity : Oversampling_Kind;
Pressure : Oversampling_Kind;
Temperature : Oversampling_Kind;
Success : out Boolean)
is
use type HAL.UInt8;
Data : HAL.UInt8;
begin
Write (Device, 16#F2#, Oversampling_Kind'Pos (Humidity), Success);
if Success then
Data := Oversampling_Kind'Pos (Temperature);
Data := Data * 8 + Oversampling_Kind'Pos (Pressure);
Data := Data * 4 + Sensor_Mode'Enum_Rep (Mode);
Write (Device, 16#F4#, Data, Success);
end if;
end Start;
end BME280.Internal;

View File

@ -0,0 +1,100 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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.Time;
generic
type Device_Context (<>) is limited private;
with procedure Read
(Device : Device_Context;
Data : out HAL.UInt8_Array;
Success : out Boolean);
-- Read the values from the BME280 chip registers into Data.
-- Each element in the Data corresponds to a specific register address
-- in the chip, so Data'Range determines the range of registers to read.
-- The value read from register X will be stored in Data(X), so
-- Data'Range should be of the Register_Address subtype.
with procedure Write
(Device : Device_Context;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
-- Write the value to the BME280 chip register with given Address.
package BME280.Internal is
function Check_Chip_Id
(Device : Device_Context;
Expect : HAL.UInt8) return Boolean;
-- Read the chip ID and check that it matches
procedure Reset
(Device : Device_Context;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean);
-- Issue a soft reset and wait until the chip is ready.
procedure Configure
(Device : Device_Context;
Standby : Standby_Duration;
Filter : IRR_Filter_Kind;
SPI_3_Wire : Boolean;
Success : out Boolean);
-- Configure the sensor to use IRR filtering and/or SPI 3-wire mode
procedure Start
(Device : Device_Context;
Mode : Sensor_Mode;
Humidity : Oversampling_Kind;
Pressure : Oversampling_Kind;
Temperature : Oversampling_Kind;
Success : out Boolean);
-- Change sensor mode. Mainly used to start one measurement or enable
-- perpetual cycling of measurements and inactive periods.
function Measuring (Device : Device_Context) return Boolean;
-- Check if a measurement is in progress
procedure Read_Measurement
(Device : Device_Context;
Value : out Measurement;
Success : out Boolean);
-- Read the raw measurement values from the sensor
procedure Read_Calibration
(Device : Device_Context;
Value : out Calibration_Constants;
Success : out Boolean);
-- Read the calibration constants from the sensor
end BME280.Internal;

View File

@ -64,22 +64,19 @@ package body BME280.SPI is
-----------
procedure Write
(Data : HAL.UInt8_Array;
(Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean)
is
use type HAL.UInt8;
use all type HAL.SPI.SPI_Status;
Addr : HAL.UInt8;
Prefix : constant HAL.UInt8 := HAL.UInt8 (Address) and 16#7F#;
Status : HAL.SPI.SPI_Status;
begin
SPI.SPI_CS.Clear;
for J in Data'Range loop
Addr := HAL.UInt8 (J) and 16#7F#;
SPI_Port.Transmit (HAL.SPI.SPI_Data_8b'(Addr, Data (J)), Status);
exit when Status /= Ok;
end loop;
SPI_Port.Transmit (HAL.SPI.SPI_Data_8b'(Prefix, Data), Status);
SPI.SPI_CS.Set;

View File

@ -0,0 +1,180 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 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 BME280.Internal;
package body BME280.SPI_Sensors is
procedure Read
(Self : BME280_SPI_Sensor'Class;
Data : out HAL.UInt8_Array;
Success : out Boolean);
procedure Write
(Self : BME280_SPI_Sensor'Class;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean);
package Sensor is
new BME280.Internal (BME280_SPI_Sensor'Class, Read, Write);
-------------------
-- Check_Chip_Id --
-------------------
overriding function Check_Chip_Id
(Self : BME280_SPI_Sensor;
Expect : HAL.UInt8 := 16#60#) return Boolean is
(Sensor.Check_Chip_Id (Self, Expect));
---------------
-- Configure --
---------------
overriding procedure Configure
(Self : BME280_SPI_Sensor;
Standby : Standby_Duration := 0.5;
Filter : IRR_Filter_Kind := Off;
SPI_3_Wire : Boolean := False;
Success : out Boolean) is
begin
Sensor.Configure (Self, Standby, Filter, SPI_3_Wire, Success);
end Configure;
overriding function Measuring (Self : BME280_SPI_Sensor) return Boolean is
(Sensor.Measuring (Self));
----------
-- Read --
----------
procedure Read
(Self : BME280_SPI_Sensor'Class;
Data : out HAL.UInt8_Array;
Success : out Boolean)
is
use type HAL.UInt8;
use all type HAL.SPI.SPI_Status;
Addr : HAL.UInt8;
Status : HAL.SPI.SPI_Status;
begin
Self.SPI_CS.Clear;
Addr := HAL.UInt8 (Data'First) or 16#80#;
Self.SPI_Port.Transmit (HAL.SPI.SPI_Data_8b'(1 => Addr), Status);
if Status = Ok then
Self.SPI_Port.Receive (HAL.SPI.SPI_Data_8b (Data), Status);
end if;
Self.SPI_CS.Set;
Success := Status = Ok;
end Read;
----------------------
-- Read_Measurement --
----------------------
overriding procedure Read_Measurement
(Self : BME280_SPI_Sensor;
Value : out Measurement;
Success : out Boolean) is
begin
Sensor.Read_Measurement (Self, Value, Success);
end Read_Measurement;
----------------------
-- Read_Calibration --
----------------------
overriding procedure Read_Calibration
(Self : in out BME280_SPI_Sensor;
Success : out Boolean) is
begin
Sensor.Read_Calibration (Self, Self.Calibration, Success);
end Read_Calibration;
-----------
-- Reset --
-----------
overriding procedure Reset
(Self : BME280_SPI_Sensor;
Timer : not null HAL.Time.Any_Delays;
Success : out Boolean) is
begin
Sensor.Reset (Self, Timer, Success);
end Reset;
-----------
-- Start --
-----------
overriding procedure Start
(Self : BME280_SPI_Sensor;
Mode : Sensor_Mode := Normal;
Humidity : Oversampling_Kind := X1;
Pressure : Oversampling_Kind := X1;
Temperature : Oversampling_Kind := X1;
Success : out Boolean) is
begin
Sensor.Start (Self, Mode, Humidity, Pressure, Temperature, Success);
end Start;
-----------
-- Write --
-----------
procedure Write
(Self : BME280_SPI_Sensor'Class;
Address : Register_Address;
Data : HAL.UInt8;
Success : out Boolean)
is
use type HAL.UInt8;
use all type HAL.SPI.SPI_Status;
Prefix : constant HAL.UInt8 := HAL.UInt8 (Address) and 16#7F#;
Status : HAL.SPI.SPI_Status;
begin
Self.SPI_CS.Clear;
Self.SPI_Port.Transmit (HAL.SPI.SPI_Data_8b'(Prefix, Data), Status);
Self.SPI_CS.Set;
Success := Status = Ok;
end Write;
end BME280.SPI_Sensors;

View File

@ -47,7 +47,7 @@ with Display_ILI9341;
with Bitmapped_Drawing;
with BMP_Fonts;
with BME280.I2C;
with BME280.I2C_Sensors;
with GUI;
with GUI_Buttons;
@ -55,9 +55,10 @@ with GUI_Buttons;
procedure Main is
use type Ada.Real_Time.Time;
package BME280_I2C is new BME280.I2C
Sensor : BME280.I2C_Sensors.BME280_I2C_Sensor :=
(I2C_Port => STM32.Device.I2C_1'Access,
I2C_Address => 16#76#);
I2C_Address => 16#76#,
Calibration => <>);
procedure Configure_Sensor;
-- Restart sensor with new settings according to GUI state
@ -68,8 +69,7 @@ procedure Main is
Press : BME280.Pressure_Pa;
end record;
function Read_Sensor
(Calib : BME280.Calibration_Constants) return Sensor_Data;
function Read_Sensor return Sensor_Data;
function Min (Left, Right : Sensor_Data) return Sensor_Data is
(Temp => BME280.Deci_Celsius'Min (Left.Temp, Right.Temp),
@ -149,7 +149,7 @@ procedure Main is
Ok : Boolean;
begin
-- Consigure IRR filter and minimal incativity delay
BME280_I2C.Sensor.Configure
Sensor.Configure
(Standby => 0.5,
Filter => Filter (GUI.State (+Fi_No .. +Fi_16)),
SPI_3_Wire => False,
@ -157,7 +157,7 @@ procedure Main is
pragma Assert (Ok);
-- Enable cycling of measurements with given oversamplig
BME280_I2C.Sensor.Start
Sensor.Start
(Mode => BME280.Normal,
Humidity => Oversampling (GUI.State (+Hu_X1 .. +Hu_16)),
Pressure => Oversampling (GUI.State (+Pr_X1 .. +Pr_16)),
@ -291,22 +291,20 @@ procedure Main is
-- Read_Sensor --
-----------------
function Read_Sensor
(Calib : BME280.Calibration_Constants) return Sensor_Data
is
function Read_Sensor return Sensor_Data is
Ok : Boolean;
Measurement : BME280.Measurement;
Temp : BME280.Deci_Celsius;
begin
BME280_I2C.Sensor.Read_Measurement (Measurement, Ok);
Sensor.Read_Measurement (Measurement, Ok);
pragma Assert (Ok);
Temp := BME280.Temperature (Measurement, Calib);
Temp := Sensor.Temperature (Measurement);
return
(Temp => Temp,
Humi => BME280.Humidity (Measurement, Temp, Calib),
Press => BME280.Pressure (Measurement, Temp, Calib));
(Temp => Temp,
Humi => Sensor.Humidity (Measurement, Temp),
Press => Sensor.Pressure (Measurement, Temp));
end Read_Sensor;
Empty : constant Sensor_Limits :=
@ -324,7 +322,6 @@ procedure Main is
Next : Ada.Real_Time.Time := Ada.Real_Time.Clock;
Ok : Boolean;
Calib : BME280.Calibration_Constants;
Next_Limits : Sensor_Limits;
begin
STM32.Board.Initialize_LEDs;
@ -347,17 +344,17 @@ begin
Clock_Speed => 400_000);
-- Look for BME280 chip
if not BME280_I2C.Sensor.Check_Chip_Id then
if not Sensor.Check_Chip_Id then
Ada.Text_IO.Put_Line ("BME280 not found.");
raise Program_Error;
end if;
-- Reset BME280
BME280_I2C.Sensor.Reset (Ravenscar_Time.Delays, Ok);
Sensor.Reset (Ravenscar_Time.Delays, Ok);
pragma Assert (Ok);
-- Read calibration data into Clib
BME280_I2C.Sensor.Read_Calibration (Calib, Ok);
Sensor.Read_Calibration (Ok);
Configure_Sensor;
@ -369,7 +366,7 @@ begin
Temperature => BME280.X1) / 1000 + 1);
-- Predict boundaries from the first sensor measurement
Next_Limits.Min := Read_Sensor (Calib);
Next_Limits.Min := Read_Sensor;
Next_Limits.Max := Next_Limits.Min;
Make_Wider (Next_Limits);
@ -385,7 +382,7 @@ begin
for X in 0 .. LCD.Width - 1 loop
STM32.Board.Toggle (STM32.Board.D1_LED);
Data := Read_Sensor (Calib);
Data := Read_Sensor;
Next_Limits :=
(Min => Min (Data, Next_Limits.Min),