aboutsummaryrefslogtreecommitdiff
path: root/hsm-ina226
diff options
context:
space:
mode:
authorPaul Oliver <contact@pauloliver.dev>2025-12-17 02:26:07 +0000
committerPaul Oliver <contact@pauloliver.dev>2025-12-20 23:35:27 +0000
commit7d7fa4816a1744d860c74a45003eda6cd71ec42a (patch)
tree45142351d64b68985c0394bf16c8ea8ba29ef979 /hsm-ina226
parent459d2c5630e1296807bbf23fd4360fb4d4f5bbe7 (diff)
Adds battery monitoring service via INA226/I2CHEADmaster
Diffstat (limited to 'hsm-ina226')
-rw-r--r--hsm-ina226/Hsm/INA226.hs114
-rw-r--r--hsm-ina226/Test/INA226.hs27
-rw-r--r--hsm-ina226/hsm-ina226.cabal40
3 files changed, 181 insertions, 0 deletions
diff --git a/hsm-ina226/Hsm/INA226.hs b/hsm-ina226/Hsm/INA226.hs
new file mode 100644
index 0000000..8862689
--- /dev/null
+++ b/hsm-ina226/Hsm/INA226.hs
@@ -0,0 +1,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
diff --git a/hsm-ina226/Test/INA226.hs b/hsm-ina226/Test/INA226.hs
new file mode 100644
index 0000000..71f8f45
--- /dev/null
+++ b/hsm-ina226/Test/INA226.hs
@@ -0,0 +1,27 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+import Control.Concurrent (threadDelay)
+import Control.Monad (forever)
+import Data.Function ((&))
+import Effectful (liftIO, runEff)
+import Hsm.Core.App (bootstrapApp)
+import Hsm.I2C (runI2C)
+import Hsm.INA226 (readINA226State, runINA226)
+import Hsm.Log (Severity (Info), logMsg, runLogsOpt)
+import Hsm.Log.Options (makeLoggerOptionParser)
+-- Import full module for cleaner `-ddump-splices` output
+-- Avoids package/module qualifiers in generated code
+import Options.Applicative
+
+type Logs = '["i2c", "ina226"]
+
+$(makeLoggerOptionParser @Logs "Options" "parser" 'Info)
+
+main :: IO ()
+main =
+ bootstrapApp parser "Launch INA226 Monitoring Test Application" $ \opts ->
+ forever (liftIO (threadDelay 1000000) >> readINA226State >>= logMsg @"ina226" Info . show)
+ & runINA226
+ & runI2C
+ & runLogsOpt @Options @Logs opts
+ & runEff
diff --git a/hsm-ina226/hsm-ina226.cabal b/hsm-ina226/hsm-ina226.cabal
new file mode 100644
index 0000000..3b25b29
--- /dev/null
+++ b/hsm-ina226/hsm-ina226.cabal
@@ -0,0 +1,40 @@
+cabal-version: 3.8
+author: Paul Oliver <contact@pauloliver.dev>
+name: hsm-ina226
+version: 0.1.0.0
+
+library
+ build-depends:
+ , base
+ , effectful-core
+ , effectful-plugin
+ , hsm-core
+ , hsm-i2c
+ , hsm-log
+
+ default-language: GHC2024
+ exposed-modules: Hsm.INA226
+ ghc-options:
+ -O2 -Wall -Werror -Wno-star-is-type -Wunused-packages
+ -fplugin=Effectful.Plugin
+
+executable test-ina226
+ build-depends:
+ , base
+ , effectful-core
+ , effectful-plugin
+ , hsm-core
+ , hsm-i2c
+ , hsm-log
+ , optparse-applicative
+
+ default-language: GHC2024
+ ghc-options:
+ -O2 -Wall -Werror -Wno-star-is-type -Wunused-packages
+ -Wno-unused-imports -fplugin=Effectful.Plugin
+
+ if !arch(x86_64)
+ ghc-options: -optl=-mno-fix-cortex-a53-835769
+
+ main-is: Test/INA226.hs
+ other-modules: Hsm.INA226