summaryrefslogtreecommitdiff
path: root/src/Automation/Car.hs
blob: 5b6623dcecb01ed18242fe43b5b3735bddd611df (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
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
{-# LANGUAGE LambdaCase, BangPatterns #-}

module Automation.Car where

import Automation.Types
import Automation.Utility
import Automation.Solar
import DataUnits
import Batteries
import Sensors

import Reactive.Banana
import Reactive.Banana.Automation
import Data.Functor.Compose
import Data.Maybe

carChargerOverrideBehavior :: Automation (Sensors t) Actuators (Behavior (Maybe PowerChange))
carChargerOverrideBehavior = fmap getOverride
	<$> (overrideBehavior =<< getEventFrom carChargerOverride)

-- | The goal is to charge the car whenever there is sufficient solar power
-- being produced.
--
-- Starting and stopping charging cycles the car's HV contactor. It does not
-- cycle under load, so probably is rated for around 100-200 thousand
-- cycles. If the car lasts 25 years, 10 cycles per day would be a
-- reasonable number.
--
-- So, this avoids stopping charging for every passing cloud. Since the
-- window where the car can charge is around 4 hours, it's reasonable to
-- check twice per hour if it can charge, and only start/stop charging then.
--
-- If it becomes cloudy, charging the car for half an hour will run the
-- house battery down some, but not a problematic amount, as long as it only
-- starts charging the car once the house's battery is well charged.
carChargingAllowed :: Automation (Sensors t) Actuators (Behavior (Maybe PowerChange))
carChargingAllowed = getCompose $ calc
	<$> Compose lowpowerMode
	<*> Compose getCurrentHour
	<*> Compose getCurrentMinute
	<*> Compose (sensedBehavior trimetricBatteryPercent)
	<*> Compose ccInputWatts
	<*> Compose batteryAmps
	<*> Compose carChargerOverrideBehavior
  where
	calc lowpower (Just (ClockSignal hour)) (Just (ClockSignal minute)) (Sensed housebattery) (Sensed solarwatts) (Sensed housebatteryamps) override
		| lowpower = Just PowerOff
		| isJust override = override
		| housebattery `belowRange` Batteries.mostlyCharged =
			Just PowerOff
		| not (minute == 0 || minute == 30) = Nothing
		-- Power on when solar is in danger of charging the
		-- battery too fast, even if it's not yet well charged.
		| housebatteryamps >= nearMaxChargeRate =
			Just PowerOn
		| housebattery `belowRange` Batteries.wellCharged hour =
			Just PowerOff
		| not (housebattery `belowRange` Batteries.fullyCharged) =
			Just PowerOn
		| solarwatts > carChargerWatts = Just PowerOn
		| otherwise = Just PowerOff
	calc _ _ _ _ _ _ _ = Just PowerOff

-- The amount used to charge the car is around 1 kw.
carChargerWatts :: Watts
carChargerWatts = Watts 1000

-- | Only charge when the car is plugged into the charger, and when the 
-- car is not already charged to its limit.
-- 
-- Getting the car SoC and charge limit needs internet access; if that is not
-- available, charge when the car is plugged in regardless.
--
-- Note that this assumes my car is the only car that will be plugged into
-- the charger. To charge another car needs a manual override.
carChargingNeeded :: Automation (Sensors t) Actuators (Behavior (Maybe Bool))
carChargingNeeded = getCompose $ calc
	<$> Compose (sensedBehavior carStateOfCharge)
	<*> Compose (sensedBehavior carChargeLimit)
	<*> Compose (sensedBehavior carPluggedIn)
  where
	calc _ _ (Sensed False) = Just False
	calc (Sensed soc) (Sensed chargelimit) (Sensed True)
		| soc < chargelimit = Just True
		| otherwise = Just False
	calc _ _ _ = Nothing

carChargerBehavior :: Automation (Sensors t) Actuators (Behavior (Maybe PowerChange))
carChargerBehavior = getCompose $ calc
	<$> Compose carChargingAllowed
	<*> Compose carChargingNeeded
	<*> Compose carChargerOverrideBehavior
  where
	calc chargingallowed chargingneeded override
		| chargingallowed == Just PowerOff = Just PowerOff
		| isJust override = override
		| chargingneeded == Just False = Just PowerOff
		| chargingallowed == Nothing = Nothing
		| chargingallowed == Just PowerOn = Just PowerOn
		| otherwise = Nothing

controlCarCharger :: Automation (Sensors t) Actuators ()
controlCarCharger = do
	b <- carChargerBehavior
	actuateBehaviorMaybe b CarCharger

-- | Turning off car charging can take a while; it's done via a weak wifi
-- link, which can need retries. So this waits for the car charger to
-- report that charging is disabled.
isCarChargerOn :: Automation (Sensors t) Actuators (Behavior (Maybe PowerChange))
isCarChargerOn = do
	carchargerb <- powerSettingBehavior (PowerSetting True)
		=<< carChargerBehavior
	enabledb <- sensedBehavior carChargerEnabled
	return $ calc <$> carchargerb <*> enabledb
  where
	calc (PowerSetting True) _ = Just PowerOn
	calc _ (Sensed True) = Nothing
	calc _ (Sensed False) = Just PowerOff
	calc _ SensorUnavailable = Nothing

offWhenCarCharging
	:: (PowerChange -> a)
	-> Automation (Sensors t) Actuators (Behavior a)
	-> Automation (Sensors t) Actuators (Behavior a)
offWhenCarCharging f getb = do
	ison <- powerSettingBehavior (PowerSetting True)
		=<< isCarChargerOn
	b <- getb
	return $ calc <$> b <*> ison
  where
	calc a (PowerSetting False) = a
	calc _ (PowerSetting True) = f PowerOff