module Propellor.Property.Journald where

import Propellor.Base
import qualified Propellor.Property.Systemd as Systemd
import Utility.DataUnits

-- | Configures journald, restarting it so the changes take effect.
configured :: Systemd.Option -> String -> Property Linux
configured :: Option -> Option -> Property Linux
configured Option
option Option
value =
	Option -> Option -> Option -> Property Linux
Systemd.configured Option
"/etc/systemd/journald.conf" Option
option Option
value
		forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Option -> Property Linux
Systemd.restarted Option
"systemd-journald"

-- The string is parsed to get a data size.
-- Examples: "100 megabytes" or "0.5tb"
type DataSize = String

configuredSize :: Systemd.Option -> DataSize -> Property Linux
configuredSize :: Option -> Option -> Property Linux
configuredSize Option
option Option
s = case [Unit] -> Option -> Maybe Integer
readSize [Unit]
dataUnits Option
s of
	Just Integer
sz -> Option -> Option -> Property Linux
configured Option
option (Integer -> Option
systemdSizeUnits Integer
sz)
	Maybe Integer
Nothing -> forall {k} (metatypes :: k).
SingI metatypes =>
Option -> Propellor Result -> Property (MetaTypes metatypes)
property (Option
"unable to parse " forall a. [a] -> [a] -> [a]
++ Option
option forall a. [a] -> [a] -> [a]
++ Option
" data size " forall a. [a] -> [a] -> [a]
++ Option
s) forall a b. (a -> b) -> a -> b
$
		forall (m :: * -> *) a. Monad m => a -> m a
return Result
FailedChange

systemMaxUse :: DataSize -> Property Linux
systemMaxUse :: Option -> Property Linux
systemMaxUse = Option -> Option -> Property Linux
configuredSize Option
"SystemMaxUse"

runtimeMaxUse :: DataSize -> Property Linux
runtimeMaxUse :: Option -> Property Linux
runtimeMaxUse = Option -> Option -> Property Linux
configuredSize Option
"RuntimeMaxUse"

systemKeepFree :: DataSize -> Property Linux
systemKeepFree :: Option -> Property Linux
systemKeepFree = Option -> Option -> Property Linux
configuredSize Option
"SystemKeepFree"

runtimeKeepFree :: DataSize -> Property Linux
runtimeKeepFree :: Option -> Property Linux
runtimeKeepFree = Option -> Option -> Property Linux
configuredSize Option
"RuntimeKeepFree"

systemMaxFileSize :: DataSize -> Property Linux
systemMaxFileSize :: Option -> Property Linux
systemMaxFileSize = Option -> Option -> Property Linux
configuredSize Option
"SystemMaxFileSize"

runtimeMaxFileSize :: DataSize -> Property Linux
runtimeMaxFileSize :: Option -> Property Linux
runtimeMaxFileSize = Option -> Option -> Property Linux
configuredSize Option
"RuntimeMaxFileSize"

-- Generates size units as used in journald.conf.
systemdSizeUnits :: Integer -> String
systemdSizeUnits :: Integer -> Option
systemdSizeUnits Integer
sz = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Char
' ') ([Unit] -> Bool -> Integer -> Option
roughSize [Unit]
cfgfileunits Bool
True Integer
sz)
  where
	cfgfileunits :: [Unit]
	cfgfileunits :: [Unit]
cfgfileunits =
	        [ Integer -> Option -> Option -> Unit
Unit (Integer -> Integer
p Integer
6) Option
"E" Option
"exabyte"
		, Integer -> Option -> Option -> Unit
Unit (Integer -> Integer
p Integer
5) Option
"P" Option
"petabyte"
		, Integer -> Option -> Option -> Unit
Unit (Integer -> Integer
p Integer
4) Option
"T" Option
"terabyte"
		, Integer -> Option -> Option -> Unit
Unit (Integer -> Integer
p Integer
3) Option
"G" Option
"gigabyte"
		, Integer -> Option -> Option -> Unit
Unit (Integer -> Integer
p Integer
2) Option
"M" Option
"megabyte"
		, Integer -> Option -> Option -> Unit
Unit (Integer -> Integer
p Integer
1) Option
"K" Option
"kilobyte"
		]
        p :: Integer -> Integer
        p :: Integer -> Integer
p Integer
n = Integer
1024forall a b. (Num a, Integral b) => a -> b -> a
^Integer
n