]> jspc29.x-matter.uni-frankfurt.de Git - padiwa.git/commitdiff
first try to implement temp sensor in amps2, IF
authorIngo Froehlich <ingo@nomail.fake>
Tue, 23 Jan 2018 10:14:10 +0000 (11:14 +0100)
committerIngo Froehlich <ingo@nomail.fake>
Tue, 23 Jan 2018 10:14:10 +0000 (11:14 +0100)
source/Amps2_Interface.vhd [new file with mode: 0644]
source/Amps2_TempSensor_UID.vhd [new file with mode: 0644]
source/i2c_master.vhd [new file with mode: 0644]

diff --git a/source/Amps2_Interface.vhd b/source/Amps2_Interface.vhd
new file mode 100644 (file)
index 0000000..1ca9ac9
--- /dev/null
@@ -0,0 +1,197 @@
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+entity interface is
+  generic(
+    clk_frequency : integer := 133_000_000;
+    i2c_frequency : integer := 13_300
+  );
+  port(
+    --System clock.
+    clk   : in std_logic;
+    reset : in std_logic;
+       temperature: out std_logic_vector(11 downto 0);
+    --I2C signals.
+    sda : inout std_logic;
+    scl : inout std_logic
+       
+  );
+end interface;
+
+architecture Behavioral of interface is
+
+  --The address of the TCS34725. This device has only one possible address,
+  --so we won't genericize it.
+        constant addr_temp_sensor  : std_logic_vector := "1001000";  
+        constant addr_UID              : std_logic_vector := "1010000";  
+  --Signals for data exchange with the core I2C controller.
+  signal temp_data_LSB,temp_data_MSB,data_UID,data_to_write, last_read_data : std_logic_vector(7 downto 0);
+  signal reading, ena, busy : std_logic;
+signal address: std_logic_vector(6 downto 0);
+
+
+  --Rising edge detect for the "controller in use" signal.
+  --A rising edge of this signal indicates that the I2C controller has accepted our data.
+  signal controller_was_in_use    : std_logic;
+  signal controller_accepted_data : std_logic;
+  
+
+  --I2C read/write constants.
+  constant write : std_logic := '0';
+  constant read  : std_logic := '1';
+
+  --I2C commands .
+  constant pointer_register : std_logic_vector := "00000000";
+
+    signal current_byte_number      : integer range 2 downto 0   := 0;
+       
+       
+  --Core state machine logic.
+  type state_type is (startup,read_UID, wait_for_temp_sensor, send_first_command,
+  wait_for_read, start_read, read_data_temp_sensor, finish_1byte_read_and_continue, 
+  finish_read_temp_sensor);
+  signal state : state_type := startup;
+
+begin
+  --
+  -- Instantiate our I2C controller.
+  --
+  I2C_CONTROLLER:
+  entity i2c_master 
+  generic map(
+    input_clk => 133_000_000, --Our system clock speed.
+    bus_clk   => 13_300
+  )  
+  port map(
+               clk       => clk,
+               reset_n   => not(reset),
+               ena       => ena,
+               addr      => address,
+               rw        => reading,
+               data_wr   => data_to_write,
+               busy      => busy,
+               data_rd   => last_read_data,
+               ack_error => open,
+               sda       => sda,
+               scl       => scl
+       );
+
+  controller_was_in_use    <= busy when rising_edge(clk);
+  controller_accepted_data <= busy and not controller_was_in_use;
+
+
+process(clk,reset)
+begin
+
+    -- If our reset signal is being driven, restar the FSM.
+    if (reset = '1') then
+      state <= startup ;
+
+    elsif rising_edge(clk) then
+
+      --Keep the following signals low unless asserted.
+      data_to_write      <= (others => '0');
+
+  case state is
+
+       when startup =>
+
+               if busy = '0' then
+                               state <= read_UID;
+               end if;
+
+
+       when read_UID =>
+          ena                  <= '1';
+          reading      <= read;
+                 address               <= addr_UID;
+
+               if controller_accepted_data = '1' then
+                               state <= wait_for_temp_sensor;
+               end if;
+
+
+       when wait_for_temp_sensor =>
+          ena                  <= '0';
+
+               if busy = '0' then
+                               state    <= send_first_command;
+                               data_UID <= last_read_data;
+               end if;
+
+
+
+       when send_first_command =>
+          ena                  <= '1';
+          reading      <= write;
+                 address               <= addr_temp_sensor;
+          data_to_write <= pointer_register;
+                 
+          --Wait here for the I2C controller to accept the new transmission, and become busy.
+               if controller_accepted_data = '1' then
+                               state <= wait_for_read;
+               end if;
+                \r      when wait_for_read =>
+               
+               ena<='0';
+               current_byte_number <=0;
+               if busy = '0' then
+                       state    <= start_read;
+               end if;
+
+       when start_read =>
+          ena              <= '1';
+          reading      <= read;
+
+          --Wait for the controller to accept the read instruction.
+               if controller_accepted_data = '1' then
+
+                       if current_byte_number = 2 then
+              state <= finish_read_temp_sensor;
+            else
+              state <= finish_1byte_read_and_continue;
+            end if;
+                       
+               end if;
+
+       when finish_1byte_read_and_continue =>
+
+          --Wait for the I2C controller to finish reading...
+               if busy = '0' then
+
+            --...capture the read result.
+               case current_byte_number is
+                       when 0 =>
+            temp_data_MSB<= last_read_data;
+                       
+                       when 1 =>
+            temp_data_LSB<= last_read_data;
+
+                       when others  =>
+                        state <= finish_read_temp_sensor;
+
+            end case;
+            --... move to the next spot in the read buffer.
+            current_byte_number <= current_byte_number + 1;
+
+            ---... and finish reading.
+            state <= start_read;
+
+               end if;
+
+       when finish_read_temp_sensor =>
+               
+       when others  =>
+               ena <= '1';
+               
+       end case; 
+       end if;
+  end process;
+
+
+temperature(11 downto 4)<=temp_data_MSB;
+temperature(3 downto 0)<=temp_data_LSB(7 downto 4);
+
+  end Behavioral;
\ No newline at end of file
diff --git a/source/Amps2_TempSensor_UID.vhd b/source/Amps2_TempSensor_UID.vhd
new file mode 100644 (file)
index 0000000..1a49f0a
--- /dev/null
@@ -0,0 +1,76 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+use ieee.std_logic_unsigned.all;
+
+library lattice;
+use lattice.components.all;
+
+entity temp_sensor_and_UID is
+  port(
+    clk   : in std_logic;
+    temperature: out std_logic_vector(11 downto 0);
+    --I2C signals.
+    sda : inout std_logic;
+    scl : inout std_logic
+  );
+end temp_sensor_and_UID;
+
+architecture Behavioral of temp_sensor_and_UID is
+   --signal clk   : std_logic;
+   signal reset :   std_logic;
+   signal count :   std_logic_vector (26 downto 0);
+   signal temporal: std_logic;
+
+   component OSCH
+      generic(
+            NOM_FREQ: string := "133");
+      port( 
+            STDBY    : in  std_logic;
+            OSC      : out std_logic;
+            SEDSTDBY : out std_logic);
+   end component;
+   
+begin
+
+--  temperature <= "1111" & x"AB";
+
+     
+  SENSOR_INTERFACE: entity interface
+  generic map(
+    clk_frequency => 133_000_000,
+    i2c_frequency => 13_300
+  )
+  port map(
+    clk             => clk,
+    reset           => reset,
+    temperature                => temperature,
+    sda             => sda,
+    scl             => scl
+  );
+
+------internal clock------------
+--OSCInst0: OSCH
+--      GENERIC MAP (NOM_FREQ  => "133")
+--      PORT MAP (STDBY => '0', OSC => clk, SEDSTDBY => OPEN);   
+
+process begin
+  wait until rising_edge(clk);
+  
+  count <= count + 1;
+  if (count(26)='1') then
+    reset <= NOT(temporal);
+    count<=(others=>'0');
+  end if;
+end process;  
+
+reset <= temporal;
+
+-------timer---------
+--TIMER: entity timer
+--  port map(
+--    clk             => clk,
+--    reset           => reset
+--  );
+
+end Behavioral;
diff --git a/source/i2c_master.vhd b/source/i2c_master.vhd
new file mode 100644 (file)
index 0000000..6c18588
--- /dev/null
@@ -0,0 +1,212 @@
+
+LIBRARY ieee;
+USE ieee.std_logic_1164.all;
+USE ieee.std_logic_unsigned.all;
+
+ENTITY i2c_master IS
+  GENERIC(
+    input_clk : INTEGER := 133_000_000; --input clock speed from user logic in Hz
+    bus_clk   : INTEGER := 13_300);     --speed the i2c bus (scl) will run at in Hz
+  PORT(
+    clk       : IN     STD_LOGIC;                    --system clock
+    reset_n   : IN     STD_LOGIC;                    --active low reset
+    ena       : IN     STD_LOGIC;                    --latch in command
+    addr      : IN     STD_LOGIC_VECTOR(6 DOWNTO 0); --address of target slave
+    rw        : IN     STD_LOGIC;                    --'0' is write, '1' is read
+    data_wr   : IN     STD_LOGIC_VECTOR(7 DOWNTO 0); --data to write to slave
+    busy      : OUT    STD_LOGIC;                    --indicates transaction in progress
+    data_rd   : OUT    STD_LOGIC_VECTOR(7 DOWNTO 0); --data read from slave
+    ack_error : BUFFER STD_LOGIC;                    --flag if improper acknowledge from slave
+    sda       : INOUT  STD_LOGIC;                    --serial data output of i2c bus
+    scl       : INOUT  STD_LOGIC);                   --serial clock output of i2c bus
+END i2c_master;
+
+ARCHITECTURE logic OF i2c_master IS
+  CONSTANT divider  :  INTEGER := (input_clk/bus_clk)/4; --number of clocks in 1/4 cycle of scl
+  TYPE machine IS(ready, start, command, slv_ack1, wr, rd, slv_ack2, mstr_ack, stop); --needed states
+  SIGNAL  state     :  machine;                          --state machine
+  SIGNAL  data_clk  :  STD_LOGIC;                        --clock edges for sda
+  SIGNAL  scl_clk   :  STD_LOGIC;                        --constantly running internal scl
+  SIGNAL  scl_ena   :  STD_LOGIC := '0';                 --enables internal scl to output
+  SIGNAL  sda_int   :  STD_LOGIC := '1';                 --internal sda
+  SIGNAL  sda_ena_n :  STD_LOGIC;                        --enables internal sda to output
+  SIGNAL  addr_rw   :  STD_LOGIC_VECTOR(7 DOWNTO 0);     --latched in address and read/write
+  SIGNAL  data_tx   :  STD_LOGIC_VECTOR(7 DOWNTO 0);     --latched in data to write to slave
+  SIGNAL  data_rx   :  STD_LOGIC_VECTOR(7 DOWNTO 0);     --data received from slave
+  SIGNAL  bit_cnt   :  INTEGER RANGE 0 TO 7 := 7;        --tracks bit number in transaction
+  SIGNAL  stretch   :  STD_LOGIC := '0';                 --identifies if slave is stretching scl
+BEGIN
+
+  --generate the timing for the bus clock (scl_clk) and the data clock (data_clk)
+  PROCESS(clk, reset_n)
+    VARIABLE count : INTEGER RANGE 0 TO divider*4; --timing for clock generation
+  BEGIN
+    IF(reset_n = '0') THEN               --reset asserted
+      stretch <= '0';
+      count := 0;
+    ELSIF(clk'EVENT AND clk = '1') THEN
+      IF(count = divider*4-1) THEN       --end of timing cycle
+        count := 0;                      --reset timer
+      ELSIF(stretch = '0') THEN          --clock stretching from slave not detected
+        count := count + 1;              --continue clock generation timing
+      END IF;
+      CASE count IS
+        WHEN 0 TO divider-1 =>           --first 1/4 cycle of clocking
+          scl_clk <= '0';
+          data_clk <= '0';
+        WHEN divider TO divider*2-1 =>   --second 1/4 cycle of clocking
+          scl_clk <= '0';
+          data_clk <= '1';
+        WHEN divider*2 TO divider*3-1 => --third 1/4 cycle of clocking
+          scl_clk <= 'Z';                --release scl
+          IF(scl = '0') THEN             --detect if slave is stretching clock
+            stretch <= '1';
+          ELSE
+            stretch <= '0';
+          END IF;
+          data_clk <= '1';
+        WHEN OTHERS =>                   --last 1/4 cycle of clocking
+          scl_clk <= 'Z';
+          data_clk <= '0';
+      END CASE;
+    END IF;
+  END PROCESS;
+
+  --state machine and writing to sda during scl low (data_clk rising edge)
+  PROCESS(data_clk, reset_n)
+  BEGIN
+    IF(reset_n = '0') THEN                  --reset asserted
+      state <= ready;                       --return to initial state
+      busy <= '1';                          --indicate not available
+      scl_ena <= '0';                       --sets scl high impedance
+      sda_int <= '1';                       --sets sda high impedance
+      bit_cnt <= 7;                         --restarts data bit counter
+      data_rd <= "00000000";                --clear data read port
+    ELSIF(data_clk'EVENT AND data_clk = '1') THEN
+      CASE state IS
+        WHEN ready =>                       --idle state
+          IF(ena = '1') THEN                --transaction requested
+            busy <= '1';                    --flag busy
+            addr_rw <= addr & rw;           --collect requested slave address and command
+            data_tx <= data_wr;             --collect requested data to write
+            state <= start;                 --go to start bit
+          ELSE                              --remain idle
+            busy <= '0';                    --unflag busy
+            state <= ready;                 --remain idle
+          END IF;
+        WHEN start =>                       --start bit of transaction
+          busy <= '1';                      --resume busy if continuous mode
+          scl_ena <= '1';                   --enable scl output
+          sda_int <= addr_rw(bit_cnt);      --set first address bit to bus
+          state <= command;                 --go to command
+        WHEN command =>                     --address and command byte of transaction
+          IF(bit_cnt = 0) THEN              --command transmit finished
+            sda_int <= '1';                 --release sda for slave acknowledge
+            bit_cnt <= 7;                   --reset bit counter for "byte" states
+            state <= slv_ack1;              --go to slave acknowledge (command)
+          ELSE                              --next clock cycle of command state
+            bit_cnt <= bit_cnt - 1;         --keep track of transaction bits
+            sda_int <= addr_rw(bit_cnt-1);  --write address/command bit to bus
+            state <= command;               --continue with command
+          END IF;
+        WHEN slv_ack1 =>                    --slave acknowledge bit (command)
+          IF(addr_rw(0) = '0') THEN         --write command
+            sda_int <= data_tx(bit_cnt);    --write first bit of data
+            state <= wr;                    --go to write byte
+          ELSE                              --read command
+            sda_int <= '1';                 --release sda from incoming data
+            state <= rd;                    --go to read byte
+          END IF;
+        WHEN wr =>                          --write byte of transaction
+          busy <= '1';                      --resume busy if continuous mode
+          IF(bit_cnt = 0) THEN              --write byte transmit finished
+            sda_int <= '1';                 --release sda for slave acknowledge
+            bit_cnt <= 7;                   --reset bit counter for "byte" states
+            state <= slv_ack2;              --go to slave acknowledge (write)
+          ELSE                              --next clock cycle of write state
+            bit_cnt <= bit_cnt - 1;         --keep track of transaction bits
+            sda_int <= data_tx(bit_cnt-1);  --write next bit to bus
+            state <= wr;                    --continue writing
+          END IF;
+        WHEN rd =>                          --read byte of transaction
+          busy <= '1';                      --resume busy if continuous mode
+          IF(bit_cnt = 0) THEN              --read byte receive finished
+            IF(ena = '1' AND rw = '1') THEN --continuing with another read
+              sda_int <= '0';               --acknowledge the byte has been received
+            ELSE                            --stopping or continuing with a write
+              sda_int <= '1';               --send a no-acknowledge (before stop or repeated start)
+            END IF;
+            bit_cnt <= 7;                   --reset bit counter for "byte" states
+            data_rd <= data_rx;             --output received data
+            state <= mstr_ack;              --go to master acknowledge
+          ELSE                              --next clock cycle of read state
+            bit_cnt <= bit_cnt - 1;         --keep track of transaction bits
+            state <= rd;                    --continue reading
+          END IF;
+        WHEN slv_ack2 =>                    --slave acknowledge bit (write)
+          IF(ena = '1') THEN                --continue transaction
+            busy <= '0';                    --continue is accepted
+            addr_rw <= addr & rw;           --collect requested slave address and command
+            data_tx <= data_wr;             --collect requested data to write
+            IF(rw = '1') THEN               --continue transaction with a read
+              state <= start;               --go to repeated start
+            ELSE                            --continue transaction with another write
+              sda_int <= data_wr(bit_cnt);  --write first bit of data
+              state <= wr;                  --go to write byte
+            END IF;
+          ELSE                              --complete transaction
+            scl_ena <= '0';                 --disable scl
+            state <= stop;                  --go to stop bit
+          END IF;
+        WHEN mstr_ack =>                    --master acknowledge bit after a read
+          IF(ena = '1') THEN                --continue transaction
+            busy <= '0';                    --continue is accepted and data received is available on bus
+            addr_rw <= addr & rw;           --collect requested slave address and command
+            data_tx <= data_wr;             --collect requested data to write
+            IF(rw = '0') THEN               --continue transaction with a write
+              state <= start;               --repeated start
+            ELSE                            --continue transaction with another read
+              sda_int <= '1';               --release sda from incoming data
+              state <= rd;                  --go to read byte
+            END IF;
+          ELSE                              --complete transaction
+            scl_ena <= '0';                 --disable scl
+            state <= stop;                  --go to stop bit
+          END IF;
+        WHEN stop =>                        --stop bit of transaction
+          busy <= '0';                      --unflag busy
+          state <= ready;                   --go to ready state
+      END CASE;    
+    END IF;
+
+    --reading from sda during scl high (falling edge of data_clk)
+    IF(reset_n = '0') THEN               --reset asserted
+      ack_error <= '0';
+    ELSIF(data_clk'EVENT AND data_clk = '0') THEN
+      CASE state IS
+        WHEN start =>                    --starting new transaction
+          ack_error <= '0';              --reset acknowledge error flag
+        WHEN slv_ack1 =>                 --receiving slave acknowledge (command)
+          ack_error <= sda OR ack_error; --set error output if no-acknowledge
+        WHEN rd =>                       --receiving slave data
+          data_rx(bit_cnt) <= sda;       --receive current slave data bit
+        WHEN slv_ack2 =>                 --receiving slave acknowledge (write)
+          ack_error <= sda OR ack_error; --set error output if no-acknowledge
+        WHEN OTHERS =>
+          NULL;
+      END CASE;
+    END IF;
+    
+  END PROCESS;  
+
+  --set sda output
+  WITH state SELECT
+    sda_ena_n <=   data_clk WHEN start, --generate start condition
+              NOT data_clk WHEN stop,   --generate stop condition
+              sda_int WHEN OTHERS;      --set to internal sda signal    
+      
+  --set scl and sda outputs
+  scl <= scl_clk WHEN scl_ena = '1' ELSE 'Z';
+  sda <= '0' WHEN sda_ena_n = '0' ELSE 'Z';
+  
+END logic;
\ No newline at end of file