aboutsummaryrefslogtreecommitdiff
path: root/hsm-ina226/Hsm/INA226.hs
blob: 8862689ae1bbfb31283a6b54118921e6ed6e6a82 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}

module Hsm.INA226
  ( INA226
  , INA226Reading (..)
  , INA226Path
  , INA226Addr
  , readINA226State
  , runINA226
  )
where

import Data.Word (Word16, Word8)
import Effectful (Dispatch (Static), DispatchOf, Eff, IOE, (:>))
import Effectful.Dispatch.Static (SideEffects (WithSideEffects), StaticRep, evalStaticRep)
import Hsm.Core.Show (showHex)
import Hsm.I2C (I2C, readInt16, readWord16, writeWord16)
import Hsm.Log (Logs, Severity (Info, Trace), logMsg)

data INA226 (a :: * -> *) (b :: *)

type instance DispatchOf INA226 = Static WithSideEffects

newtype instance StaticRep INA226
  = INA226 ()

data INA226Reading = INA226Reading
  { voltage :: Float
  , current :: Float
  , power :: Float
  }
  deriving Show

-- INA226 I2C device path and address
type INA226Path = "/dev/i2c-0"

type INA226Addr = 64

-- INA226 registers
configurationReg :: Word8
configurationReg = 0x00

busVoltageReg :: Word8
busVoltageReg = 0x02

powerReg :: Word8
powerReg = 0x03

currentReg :: Word8
currentReg = 0x04

calibratonReg :: Word8
calibratonReg = 0x05

manufacturerIdReg :: Word8
manufacturerIdReg = 0xfe

dieIdReg :: Word8
dieIdReg = 0xff

-- Configuration and calibration constants
-- For reference, data sheet can be found here:
-- https://www.ti.com/lit/ds/symlink/ina226.pdf
reset :: Word16
reset = 0b1000000000000000

-- Average values over 16 samples
-- Use a 1.1ms conversion time for bus voltage and shunt voltage readings
-- Use continuous shunt and bus voltage operating mode
configuration :: Word16
configuration = 0b0000010100100111

-- Decide LSB for current readings based on expected max current:
-- CurrentLSB == max_expected_current / 2^15 == 5A / 2^15 == 0.2mA/bit (rounded up)
currentLSB :: Float
currentLSB = 0.0002

-- PowerLSB = CurrentLSB * 25
powerLSB :: Float
powerLSB = currentLSB * 25

-- Calibration == 0.00512 / (CurrentLSB * Rshunt) == 0.00512 / (0.0002 * 0.002) == 12800
calibration :: Word16
calibration = 12800

-- Voltage LSB is fixed
busVoltageLSB :: Float
busVoltageLSB = 0.00125

-- Read INA226 voltage/current/power registers
readINA226State :: (I2C INA226Path INA226Addr :> es, INA226 :> es, Logs '["i2c", "ina226"] es) => Eff es INA226Reading
readINA226State = do
  logMsg @"ina226" Trace "Reading INA226 state registers"
  voltage <- (* busVoltageLSB) . fromIntegral <$> readWord16 busVoltageReg
  current <- (* currentLSB) . fromIntegral <$> readInt16 currentReg
  power <- (* powerLSB) . fromIntegral <$> readInt16 powerReg
  return INA226Reading{..}

runINA226
  :: (I2C INA226Path INA226Addr :> es, IOE :> es, Logs '["i2c", "ina226"] es) => Eff (INA226 : es) a -> Eff es a
runINA226 action = do
  -- Prepare chip
  writeWord16 configurationReg reset
  writeWord16 configurationReg configuration
  writeWord16 calibratonReg calibration
  -- Print some stats to the user
  manId <- readWord16 manufacturerIdReg
  dieId <- readWord16 dieIdReg
  cfgReg <- readWord16 configurationReg
  logMsg @"ina226" Info $ "INA226 manufacturer ID: " <> showHex manId
  logMsg @"ina226" Info $ "INA226 die ID: " <> showHex dieId
  logMsg @"ina226" Info $ "INA226 configuration register: " <> showHex cfgReg
  evalStaticRep (INA226 ()) action