module Propellor.Property.Laptop where
import Propellor.Base
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Systemd as Systemd
powertopAutoTuneOnBoot :: RevertableProperty DebianLike DebianLike
powertopAutoTuneOnBoot :: RevertableProperty DebianLike DebianLike
powertopAutoTuneOnBoot = Property DebianLike
setup forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property DebianLike
undo
	forall p. IsProp p => p -> Desc -> p
`describe` Desc
"powertop auto-tune on boot"
  where
	setup :: CombinedType (Property DebianLike) (Property UnixLike)
setup = Desc -> Property Linux
Systemd.enabled Desc
"powertop"
		forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Desc] -> Property DebianLike
Apt.installed [Desc
"powertop"]
		forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
servicefile
			[ Desc
"[Unit]"
			, Desc
"Description=Powertop tunings"
			, Desc
"[Service]"
			, Desc
"ExecStart=/usr/sbin/powertop --auto-tune"
			, Desc
"RemainAfterExit=true"
			, Desc
"[Install]"
			, Desc
"WantedBy=multi-user.target"
			]
	undo :: Property DebianLike
undo = forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets forall a b. (a -> b) -> a -> b
$ Desc -> Property UnixLike
File.notPresent Desc
servicefile
		forall x y. Combines x y => x -> y -> CombinedType x y
`requires` forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Desc -> IO Bool
doesFileExist Desc
servicefile)
			(Desc -> Property Linux
Systemd.disabled Desc
"powertop")
	servicefile :: Desc
servicefile = Desc
"/etc/systemd/system/powertop.service"
trimSSD :: Property Linux
trimSSD :: Property Linux
trimSSD = Desc -> Property Linux
Systemd.enabled Desc
"fstrim.timer"