Added journald configuration properties.
This commit is contained in:
parent
8556f94fbf
commit
fa66cb49d6
|
@ -6,6 +6,7 @@ propellor (1.4.0) UNRELEASED; urgency=medium
|
||||||
(API change)
|
(API change)
|
||||||
* Fix info propigation from fallback combinator's second Property.
|
* Fix info propigation from fallback combinator's second Property.
|
||||||
* Added systemd configuration properties.
|
* Added systemd configuration properties.
|
||||||
|
* Added journald configuration properties.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Thu, 15 Jan 2015 20:14:29 -0400
|
-- Joey Hess <id@joeyh.name> Thu, 15 Jan 2015 20:14:29 -0400
|
||||||
|
|
||||||
|
|
|
@ -100,6 +100,7 @@ Library
|
||||||
Propellor.Property.Sudo
|
Propellor.Property.Sudo
|
||||||
Propellor.Property.Systemd
|
Propellor.Property.Systemd
|
||||||
Propellor.Property.Systemd.Core
|
Propellor.Property.Systemd.Core
|
||||||
|
Propellor.Property.Systemd.Journald
|
||||||
Propellor.Property.Tor
|
Propellor.Property.Tor
|
||||||
Propellor.Property.User
|
Propellor.Property.User
|
||||||
Propellor.Property.HostingProvider.CloudAtCost
|
Propellor.Property.HostingProvider.CloudAtCost
|
||||||
|
@ -136,11 +137,13 @@ Library
|
||||||
Propellor.Property.Chroot.Util
|
Propellor.Property.Chroot.Util
|
||||||
Utility.Applicative
|
Utility.Applicative
|
||||||
Utility.Data
|
Utility.Data
|
||||||
|
Utility.DataUnits
|
||||||
Utility.Directory
|
Utility.Directory
|
||||||
Utility.Env
|
Utility.Env
|
||||||
Utility.Exception
|
Utility.Exception
|
||||||
Utility.FileMode
|
Utility.FileMode
|
||||||
Utility.FileSystemEncoding
|
Utility.FileSystemEncoding
|
||||||
|
Utility.HumanNumber
|
||||||
Utility.LinuxMkLibs
|
Utility.LinuxMkLibs
|
||||||
Utility.Misc
|
Utility.Misc
|
||||||
Utility.Monad
|
Utility.Monad
|
||||||
|
|
|
@ -0,0 +1,54 @@
|
||||||
|
module Propellor.Property.Systemd.Journald where
|
||||||
|
import Propellor
|
||||||
|
import qualified Propellor.Property.Systemd as Systemd
|
||||||
|
import qualified Propellor.Property.File as File
|
||||||
|
import Utility.DataUnits
|
||||||
|
|
||||||
|
-- | Configures journald, restarting it so the changes take effect.
|
||||||
|
configured :: Systemd.Option -> String -> Property
|
||||||
|
configured option value =
|
||||||
|
Systemd.configured "/etc/systemd/journald.conf" option value
|
||||||
|
`onChange` Systemd.restarted "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
|
||||||
|
configuredSize option s = case readSize dataUnits s of
|
||||||
|
Just sz -> configured option (systemdSizeUnits sz)
|
||||||
|
Nothing -> property ("unable to parse " ++ option ++ " data size " ++ s) noChange
|
||||||
|
|
||||||
|
systemMaxUse :: DataSize -> Property
|
||||||
|
systemMaxUse = configuredSize "SystemMaxUse"
|
||||||
|
|
||||||
|
runtimeMaxUse :: DataSize -> Property
|
||||||
|
runtimeMaxUse = configuredSize "RuntimeMaxUse"
|
||||||
|
|
||||||
|
systemKeepFree :: DataSize -> Property
|
||||||
|
systemKeepFree = configuredSize "SystemKeepFree"
|
||||||
|
|
||||||
|
runtimeKeepFree :: DataSize -> Property
|
||||||
|
runtimeKeepFree = configuredSize "RuntimeKeepFree"
|
||||||
|
|
||||||
|
systemMaxFileSize :: DataSize -> Property
|
||||||
|
systemMaxFileSize = configuredSize "SystemMaxFileSize"
|
||||||
|
|
||||||
|
runtimeMaxFileSize :: DataSize -> Property
|
||||||
|
runtimeMaxFileSize = configuredSize "RuntimeMaxFileSize"
|
||||||
|
|
||||||
|
-- Generates size units as used in journald.conf.
|
||||||
|
systemdSizeUnits :: Integer -> String
|
||||||
|
systemdSizeUnits n = filter (/= ' ') (roughSize cfgfileunits True n)
|
||||||
|
where
|
||||||
|
cfgfileunits :: [Unit]
|
||||||
|
cfgfileunits =
|
||||||
|
[ Unit (p 6) "E" "exabyte"
|
||||||
|
, Unit (p 5) "P" "petabyte"
|
||||||
|
, Unit (p 4) "T" "terabyte"
|
||||||
|
, Unit (p 3) "G" "gigabyte"
|
||||||
|
, Unit (p 2) "M" "megabyte"
|
||||||
|
, Unit (p 1) "K" "kilobyte"
|
||||||
|
]
|
||||||
|
p :: Integer -> Integer
|
||||||
|
p n = 1024^n
|
|
@ -0,0 +1,161 @@
|
||||||
|
{- data size display and parsing
|
||||||
|
-
|
||||||
|
- Copyright 2011 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- License: BSD-2-clause
|
||||||
|
-
|
||||||
|
-
|
||||||
|
- And now a rant:
|
||||||
|
-
|
||||||
|
- In the beginning, we had powers of two, and they were good.
|
||||||
|
-
|
||||||
|
- Disk drive manufacturers noticed that some powers of two were
|
||||||
|
- sorta close to some powers of ten, and that rounding down to the nearest
|
||||||
|
- power of ten allowed them to advertise their drives were bigger. This
|
||||||
|
- was sorta annoying.
|
||||||
|
-
|
||||||
|
- Then drives got big. Really, really big. This was good.
|
||||||
|
-
|
||||||
|
- Except that the small rounding error perpretrated by the drive
|
||||||
|
- manufacturers suffered the fate of a small error, and became a large
|
||||||
|
- error. This was bad.
|
||||||
|
-
|
||||||
|
- So, a committee was formed. And it arrived at a committee-like decision,
|
||||||
|
- which satisfied noone, confused everyone, and made the world an uglier
|
||||||
|
- place. As with all committees, this was meh.
|
||||||
|
-
|
||||||
|
- And the drive manufacturers happily continued selling drives that are
|
||||||
|
- increasingly smaller than you'd expect, if you don't count on your
|
||||||
|
- fingers. But that are increasingly too big for anyone to much notice.
|
||||||
|
- This caused me to need git-annex.
|
||||||
|
-
|
||||||
|
- Thus, I use units here that I loathe. Because if I didn't, people would
|
||||||
|
- be confused that their drives seem the wrong size, and other people would
|
||||||
|
- complain at me for not being standards compliant. And we call this
|
||||||
|
- progress?
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Utility.DataUnits (
|
||||||
|
dataUnits,
|
||||||
|
storageUnits,
|
||||||
|
memoryUnits,
|
||||||
|
bandwidthUnits,
|
||||||
|
oldSchoolUnits,
|
||||||
|
Unit(..),
|
||||||
|
|
||||||
|
roughSize,
|
||||||
|
compareSizes,
|
||||||
|
readSize
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.List
|
||||||
|
import Data.Char
|
||||||
|
|
||||||
|
import Utility.HumanNumber
|
||||||
|
|
||||||
|
type ByteSize = Integer
|
||||||
|
type Name = String
|
||||||
|
type Abbrev = String
|
||||||
|
data Unit = Unit ByteSize Abbrev Name
|
||||||
|
deriving (Ord, Show, Eq)
|
||||||
|
|
||||||
|
dataUnits :: [Unit]
|
||||||
|
dataUnits = storageUnits ++ memoryUnits
|
||||||
|
|
||||||
|
{- Storage units are (stupidly) powers of ten. -}
|
||||||
|
storageUnits :: [Unit]
|
||||||
|
storageUnits =
|
||||||
|
[ Unit (p 8) "YB" "yottabyte"
|
||||||
|
, Unit (p 7) "ZB" "zettabyte"
|
||||||
|
, Unit (p 6) "EB" "exabyte"
|
||||||
|
, Unit (p 5) "PB" "petabyte"
|
||||||
|
, Unit (p 4) "TB" "terabyte"
|
||||||
|
, Unit (p 3) "GB" "gigabyte"
|
||||||
|
, Unit (p 2) "MB" "megabyte"
|
||||||
|
, Unit (p 1) "kB" "kilobyte" -- weird capitalization thanks to committe
|
||||||
|
, Unit (p 0) "B" "byte"
|
||||||
|
]
|
||||||
|
where
|
||||||
|
p :: Integer -> Integer
|
||||||
|
p n = 1000^n
|
||||||
|
|
||||||
|
{- Memory units are (stupidly named) powers of 2. -}
|
||||||
|
memoryUnits :: [Unit]
|
||||||
|
memoryUnits =
|
||||||
|
[ Unit (p 8) "YiB" "yobibyte"
|
||||||
|
, Unit (p 7) "ZiB" "zebibyte"
|
||||||
|
, Unit (p 6) "EiB" "exbibyte"
|
||||||
|
, Unit (p 5) "PiB" "pebibyte"
|
||||||
|
, Unit (p 4) "TiB" "tebibyte"
|
||||||
|
, Unit (p 3) "GiB" "gibibyte"
|
||||||
|
, Unit (p 2) "MiB" "mebibyte"
|
||||||
|
, Unit (p 1) "KiB" "kibibyte"
|
||||||
|
, Unit (p 0) "B" "byte"
|
||||||
|
]
|
||||||
|
where
|
||||||
|
p :: Integer -> Integer
|
||||||
|
p n = 2^(n*10)
|
||||||
|
|
||||||
|
{- Bandwidth units are only measured in bits if you're some crazy telco. -}
|
||||||
|
bandwidthUnits :: [Unit]
|
||||||
|
bandwidthUnits = error "stop trying to rip people off"
|
||||||
|
|
||||||
|
{- Do you yearn for the days when men were men and megabytes were megabytes? -}
|
||||||
|
oldSchoolUnits :: [Unit]
|
||||||
|
oldSchoolUnits = zipWith (curry mingle) storageUnits memoryUnits
|
||||||
|
where
|
||||||
|
mingle (Unit _ a n, Unit s' _ _) = Unit s' a n
|
||||||
|
|
||||||
|
{- approximate display of a particular number of bytes -}
|
||||||
|
roughSize :: [Unit] -> Bool -> ByteSize -> String
|
||||||
|
roughSize units short i
|
||||||
|
| i < 0 = '-' : findUnit units' (negate i)
|
||||||
|
| otherwise = findUnit units' i
|
||||||
|
where
|
||||||
|
units' = sortBy (flip compare) units -- largest first
|
||||||
|
|
||||||
|
findUnit (u@(Unit s _ _):us) i'
|
||||||
|
| i' >= s = showUnit i' u
|
||||||
|
| otherwise = findUnit us i'
|
||||||
|
findUnit [] i' = showUnit i' (last units') -- bytes
|
||||||
|
|
||||||
|
showUnit x (Unit size abbrev name) = s ++ " " ++ unit
|
||||||
|
where
|
||||||
|
v = (fromInteger x :: Double) / fromInteger size
|
||||||
|
s = showImprecise 2 v
|
||||||
|
unit
|
||||||
|
| short = abbrev
|
||||||
|
| s == "1" = name
|
||||||
|
| otherwise = name ++ "s"
|
||||||
|
|
||||||
|
{- displays comparison of two sizes -}
|
||||||
|
compareSizes :: [Unit] -> Bool -> ByteSize -> ByteSize -> String
|
||||||
|
compareSizes units abbrev old new
|
||||||
|
| old > new = roughSize units abbrev (old - new) ++ " smaller"
|
||||||
|
| old < new = roughSize units abbrev (new - old) ++ " larger"
|
||||||
|
| otherwise = "same"
|
||||||
|
|
||||||
|
{- Parses strings like "10 kilobytes" or "0.5tb". -}
|
||||||
|
readSize :: [Unit] -> String -> Maybe ByteSize
|
||||||
|
readSize units input
|
||||||
|
| null parsednum || null parsedunit = Nothing
|
||||||
|
| otherwise = Just $ round $ number * fromIntegral multiplier
|
||||||
|
where
|
||||||
|
(number, rest) = head parsednum
|
||||||
|
multiplier = head parsedunit
|
||||||
|
unitname = takeWhile isAlpha $ dropWhile isSpace rest
|
||||||
|
|
||||||
|
parsednum = reads input :: [(Double, String)]
|
||||||
|
parsedunit = lookupUnit units unitname
|
||||||
|
|
||||||
|
lookupUnit _ [] = [1] -- no unit given, assume bytes
|
||||||
|
lookupUnit [] _ = []
|
||||||
|
lookupUnit (Unit s a n:us) v
|
||||||
|
| a ~~ v || n ~~ v = [s]
|
||||||
|
| plural n ~~ v || a ~~ byteabbrev v = [s]
|
||||||
|
| otherwise = lookupUnit us v
|
||||||
|
|
||||||
|
a ~~ b = map toLower a == map toLower b
|
||||||
|
|
||||||
|
plural n = n ++ "s"
|
||||||
|
byteabbrev a = a ++ "b"
|
|
@ -0,0 +1,21 @@
|
||||||
|
{- numbers for humans
|
||||||
|
-
|
||||||
|
- Copyright 2012-2013 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- License: BSD-2-clause
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Utility.HumanNumber where
|
||||||
|
|
||||||
|
{- Displays a fractional value as a string with a limited number
|
||||||
|
- of decimal digits. -}
|
||||||
|
showImprecise :: RealFrac a => Int -> a -> String
|
||||||
|
showImprecise precision n
|
||||||
|
| precision == 0 || remainder == 0 = show (round n :: Integer)
|
||||||
|
| otherwise = show int ++ "." ++ striptrailing0s (pad0s $ show remainder)
|
||||||
|
where
|
||||||
|
int :: Integer
|
||||||
|
(int, frac) = properFraction n
|
||||||
|
remainder = round (frac * 10 ^ precision) :: Integer
|
||||||
|
pad0s s = replicate (precision - length s) '0' ++ s
|
||||||
|
striptrailing0s = reverse . dropWhile (== '0') . reverse
|
Loading…
Reference in New Issue