Merge Utiity modules from git-annex.

Except for a few that are using the other exception handling library,
that propellor has not switched to yet.
This commit is contained in:
Joey Hess 2015-01-06 19:07:40 -04:00
parent f4a57ca27d
commit 16a5f561f5
17 changed files with 85 additions and 76 deletions

1
debian/changelog vendored
View File

@ -1,6 +1,7 @@
propellor (1.3.2) UNRELEASED; urgency=medium propellor (1.3.2) UNRELEASED; urgency=medium
* SSHFP records are also generated for CNAMES of hosts. * SSHFP records are also generated for CNAMES of hosts.
* Merge Utiity modules from git-annex.
-- Joey Hess <id@joeyh.name> Sun, 04 Jan 2015 21:25:42 -0400 -- Joey Hess <id@joeyh.name> Sun, 04 Jan 2015 21:25:42 -0400

View File

@ -17,7 +17,6 @@ import qualified Propellor.Property.Apache as Apache
import qualified Propellor.Property.Postfix as Postfix import qualified Propellor.Property.Postfix as Postfix
import Utility.SafeCommand import Utility.SafeCommand
import Utility.FileMode import Utility.FileMode
import Utility.Path
import Data.List import Data.List
import System.Posix.Files import System.Posix.Files
@ -313,6 +312,7 @@ twitRss = combineProperties "twitter rss"
"./twitRss " ++ shellEscape url ++ " > " ++ shellEscape ("../" ++ desc ++ ".rss") "./twitRss " ++ shellEscape url ++ " > " ++ shellEscape ("../" ++ desc ++ ".rss")
-- Work around for expired ssl cert. -- Work around for expired ssl cert.
-- (no longer expired, TODO remove this and change urls)
pumpRss :: Property pumpRss :: Property
pumpRss = Cron.job "pump rss" "15 * * * *" "joey" "/srv/web/tmp.kitenet.net/" pumpRss = Cron.job "pump rss" "15 * * * *" "joey" "/srv/web/tmp.kitenet.net/"
"wget https://pump2rss.com/feed/joeyh@identi.ca.atom -O pump.atom --no-check-certificate 2>/dev/null" "wget https://pump2rss.com/feed/joeyh@identi.ca.atom -O pump.atom --no-check-certificate 2>/dev/null"
@ -321,7 +321,7 @@ ircBouncer :: Property
ircBouncer = propertyList "IRC bouncer" ircBouncer = propertyList "IRC bouncer"
[ Apt.installed ["znc"] [ Apt.installed ["znc"]
, User.accountFor "znc" , User.accountFor "znc"
, File.dirExists (parentDir conf) , File.dirExists (takeDirectory conf)
, File.hasPrivContent conf anyContext , File.hasPrivContent conf anyContext
, File.ownerGroup conf "znc" "znc" , File.ownerGroup conf "znc" "znc"
, Cron.job "znconboot" "@reboot" "znc" "~" "znc" , Cron.job "znconboot" "@reboot" "znc" "~" "znc"

View File

@ -9,7 +9,6 @@ module Propellor.Shim (setup, cleanEnv, file) where
import Propellor import Propellor
import Utility.LinuxMkLibs import Utility.LinuxMkLibs
import Utility.SafeCommand import Utility.SafeCommand
import Utility.Path
import Utility.FileMode import Utility.FileMode
import Utility.FileSystemEncoding import Utility.FileSystemEncoding
@ -34,7 +33,7 @@ setup propellorbin propellorbinpath dest = checkAlreadyShimmed propellorbin $ do
let linker = (dest ++) $ let linker = (dest ++) $
fromMaybe (error "cannot find ld-linux linker") $ fromMaybe (error "cannot find ld-linux linker") $
headMaybe $ filter ("ld-linux" `isInfixOf`) libs' headMaybe $ filter ("ld-linux" `isInfixOf`) libs'
let gconvdir = (dest ++) $ parentDir $ let gconvdir = (dest ++) $ takeDirectory $
fromMaybe (error "cannot find gconv directory") $ fromMaybe (error "cannot find gconv directory") $
headMaybe $ filter ("/gconv/" `isInfixOf`) glibclibs headMaybe $ filter ("/gconv/" `isInfixOf`) glibclibs
let linkerparams = ["--library-path", intercalate ":" libdirs ] let linkerparams = ["--library-path", intercalate ":" libdirs ]
@ -75,5 +74,5 @@ installFile top f = do
createLink f dest `catchIO` (const copy) createLink f dest `catchIO` (const copy)
where where
copy = void $ boolSystem "cp" [Param "-a", Param f, Param dest] copy = void $ boolSystem "cp" [Param "-a", Param f, Param dest]
destdir = inTop top $ parentDir f destdir = inTop top $ takeDirectory f
dest = inTop top f dest = inTop top f

View File

@ -1,6 +1,6 @@
{- applicative stuff {- applicative stuff
- -
- Copyright 2012 Joey Hess <id@joeyh.name> - Copyright 2012 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- utilities for simple data types {- utilities for simple data types
- -
- Copyright 2013 Joey Hess <id@joeyh.name> - Copyright 2013 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- portable environment variables {- portable environment variables
- -
- Copyright 2013 Joey Hess <id@joeyh.name> - Copyright 2013 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
@ -14,6 +14,7 @@ import Utility.Exception
import Control.Applicative import Control.Applicative
import Data.Maybe import Data.Maybe
import qualified System.Environment as E import qualified System.Environment as E
import qualified System.SetEnv
#else #else
import qualified System.Posix.Env as PE import qualified System.Posix.Env as PE
#endif #endif
@ -39,27 +40,27 @@ getEnvironment = PE.getEnvironment
getEnvironment = E.getEnvironment getEnvironment = E.getEnvironment
#endif #endif
{- Returns True if it could successfully set the environment variable. {- Sets an environment variable. To overwrite an existing variable,
- overwrite must be True.
- -
- There is, apparently, no way to do this in Windows. Instead, - On Windows, setting a variable to "" unsets it. -}
- environment varuables must be provided when running a new process. -} setEnv :: String -> String -> Bool -> IO ()
setEnv :: String -> String -> Bool -> IO Bool
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
setEnv var val overwrite = do setEnv var val overwrite = PE.setEnv var val overwrite
PE.setEnv var val overwrite
return True
#else #else
setEnv _ _ _ = return False setEnv var val True = System.SetEnv.setEnv var val
setEnv var val False = do
r <- getEnv var
case r of
Nothing -> setEnv var val True
Just _ -> return ()
#endif #endif
{- Returns True if it could successfully unset the environment variable. -} unsetEnv :: String -> IO ()
unsetEnv :: String -> IO Bool
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
unsetEnv var = do unsetEnv = PE.unsetEnv
PE.unsetEnv var
return True
#else #else
unsetEnv _ = return False unsetEnv = System.SetEnv.unsetEnv
#endif #endif
{- Adds the environment variable to the input environment. If already {- Adds the environment variable to the input environment. If already

View File

@ -1,6 +1,6 @@
{- GHC File system encoding handling. {- GHC File system encoding handling.
- -
- Copyright 2012-2014 Joey Hess <id@joeyh.name> - Copyright 2012-2014 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
@ -111,7 +111,7 @@ truncateFilePath :: Int -> FilePath -> FilePath
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
truncateFilePath n = go . reverse truncateFilePath n = go . reverse
where where
go f = go f =
let bytes = decodeW8 f let bytes = decodeW8 f
in if length bytes <= n in if length bytes <= n
then reverse f then reverse f

View File

@ -1,6 +1,6 @@
{- Linux library copier and binary shimmer {- Linux library copier and binary shimmer
- -
- Copyright 2013 Joey Hess <id@joeyh.name> - Copyright 2013 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
@ -10,6 +10,7 @@ module Utility.LinuxMkLibs where
import Control.Applicative import Control.Applicative
import Data.Maybe import Data.Maybe
import System.Directory import System.Directory
import System.FilePath
import Data.List.Utils import Data.List.Utils
import System.Posix.Files import System.Posix.Files
import Data.Char import Data.Char
@ -28,14 +29,14 @@ installLib installfile top lib = ifM (doesFileExist lib)
( do ( do
installfile top lib installfile top lib
checksymlink lib checksymlink lib
return $ Just $ parentDir lib return $ Just $ takeDirectory lib
, return Nothing , return Nothing
) )
where where
checksymlink f = whenM (isSymbolicLink <$> getSymbolicLinkStatus (inTop top f)) $ do checksymlink f = whenM (isSymbolicLink <$> getSymbolicLinkStatus (inTop top f)) $ do
l <- readSymbolicLink (inTop top f) l <- readSymbolicLink (inTop top f)
let absl = absPathFrom (parentDir f) l let absl = absPathFrom (takeDirectory f) l
let target = relPathDirToFile (parentDir f) absl let target = relPathDirToFile (takeDirectory f) absl
installfile top absl installfile top absl
nukeFile (top ++ f) nukeFile (top ++ f)
createSymbolicLink target (inTop top f) createSymbolicLink target (inTop top f)

View File

@ -1,6 +1,6 @@
{- misc utility functions {- misc utility functions
- -
- Copyright 2010-2011 Joey Hess <id@joeyh.name> - Copyright 2010-2011 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- monadic stuff {- monadic stuff
- -
- Copyright 2010-2012 Joey Hess <id@joeyh.name> - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- path manipulation {- path manipulation
- -
- Copyright 2010-2014 Joey Hess <id@joeyh.name> - Copyright 2010-2014 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
@ -21,6 +21,7 @@ import Control.Applicative
import qualified System.FilePath.Posix as Posix import qualified System.FilePath.Posix as Posix
#else #else
import System.Posix.Files import System.Posix.Files
import Utility.Exception
#endif #endif
import qualified "MissingH" System.Path as MissingH import qualified "MissingH" System.Path as MissingH
@ -76,14 +77,12 @@ absNormPathUnix dir path = todos <$> MissingH.absNormPath (fromdos dir) (fromdos
todos = replace "/" "\\" todos = replace "/" "\\"
#endif #endif
{- Returns the parent directory of a path. {- Just the parent directory of a path, or Nothing if the path has no
- - parent (ie for "/") -}
- To allow this to be easily used in loops, which terminate upon reaching the parentDir :: FilePath -> Maybe FilePath
- top, the parent of / is "" -}
parentDir :: FilePath -> FilePath
parentDir dir parentDir dir
| null dirs = "" | null dirs = Nothing
| otherwise = joinDrive drive (join s $ init dirs) | otherwise = Just $ joinDrive drive (join s $ init dirs)
where where
-- on Unix, the drive will be "/" when the dir is absolute, otherwise "" -- on Unix, the drive will be "/" when the dir is absolute, otherwise ""
(drive, path) = splitDrive dir (drive, path) = splitDrive dir
@ -93,8 +92,8 @@ parentDir dir
prop_parentDir_basics :: FilePath -> Bool prop_parentDir_basics :: FilePath -> Bool
prop_parentDir_basics dir prop_parentDir_basics dir
| null dir = True | null dir = True
| dir == "/" = parentDir dir == "" | dir == "/" = parentDir dir == Nothing
| otherwise = p /= dir | otherwise = p /= Just dir
where where
p = parentDir dir p = parentDir dir
@ -235,11 +234,11 @@ toCygPath p
| null drive = recombine parts | null drive = recombine parts
| otherwise = recombine $ "/cygdrive" : driveletter drive : parts | otherwise = recombine $ "/cygdrive" : driveletter drive : parts
where where
(drive, p') = splitDrive p (drive, p') = splitDrive p
parts = splitDirectories p' parts = splitDirectories p'
driveletter = map toLower . takeWhile (/= ':') driveletter = map toLower . takeWhile (/= ':')
recombine = fixtrailing . Posix.joinPath recombine = fixtrailing . Posix.joinPath
fixtrailing s fixtrailing s
| hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s | hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s
| otherwise = s | otherwise = s
#endif #endif
@ -255,7 +254,9 @@ fileNameLengthLimit :: FilePath -> IO Int
fileNameLengthLimit _ = return 255 fileNameLengthLimit _ = return 255
#else #else
fileNameLengthLimit dir = do fileNameLengthLimit dir = do
l <- fromIntegral <$> getPathVar dir FileNameLimit -- getPathVar can fail due to statfs(2) overflow
l <- catchDefaultIO 0 $
fromIntegral <$> getPathVar dir FileNameLimit
if l <= 0 if l <= 0
then return 255 then return 255
else return $ minimum [l, 255] else return $ minimum [l, 255]
@ -267,12 +268,13 @@ fileNameLengthLimit dir = do
- sane FilePath. - sane FilePath.
- -
- All spaces and punctuation and other wacky stuff are replaced - All spaces and punctuation and other wacky stuff are replaced
- with '_', except for '.' "../" will thus turn into ".._", which is safe. - with '_', except for '.'
- "../" will thus turn into ".._", which is safe.
-} -}
sanitizeFilePath :: String -> FilePath sanitizeFilePath :: String -> FilePath
sanitizeFilePath = map sanitize sanitizeFilePath = map sanitize
where where
sanitize c sanitize c
| c == '.' = c | c == '.' = c
| isSpace c || isPunctuation c || isSymbol c || isControl c || c == '/' = '_' | isSpace c || isPunctuation c || isSymbol c || isControl c || c == '/' = '_'
| otherwise = c | otherwise = c

View File

@ -2,7 +2,7 @@
- -
- This is like System.PosixCompat.Files, except with a fixed rename. - This is like System.PosixCompat.Files, except with a fixed rename.
- -
- Copyright 2014 Joey Hess <id@joeyh.name> - Copyright 2014 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- QuickCheck with additional instances {- QuickCheck with additional instances
- -
- Copyright 2012-2014 Joey Hess <id@joeyh.name> - Copyright 2012-2014 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- safely running shell commands {- safely running shell commands
- -
- Copyright 2010-2013 Joey Hess <id@joeyh.name> - Copyright 2010-2013 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}

View File

@ -1,6 +1,6 @@
{- scheduled activities {- scheduled activities
- -
- Copyright 2013-2014 Joey Hess <id@joeyh.name> - Copyright 2013-2014 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
@ -44,7 +44,7 @@ import Data.Char
{- Some sort of scheduled event. -} {- Some sort of scheduled event. -}
data Schedule = Schedule Recurrance ScheduledTime data Schedule = Schedule Recurrance ScheduledTime
deriving (Eq, Read, Show, Ord) deriving (Eq, Read, Show, Ord)
data Recurrance data Recurrance
= Daily = Daily
@ -54,7 +54,7 @@ data Recurrance
| Divisible Int Recurrance | Divisible Int Recurrance
-- ^ Days, Weeks, or Months of the year evenly divisible by a number. -- ^ Days, Weeks, or Months of the year evenly divisible by a number.
-- (Divisible Year is years evenly divisible by a number.) -- (Divisible Year is years evenly divisible by a number.)
deriving (Eq, Read, Show, Ord) deriving (Eq, Read, Show, Ord)
type WeekDay = Int type WeekDay = Int
type MonthDay = Int type MonthDay = Int
@ -63,7 +63,7 @@ type YearDay = Int
data ScheduledTime data ScheduledTime
= AnyTime = AnyTime
| SpecificTime Hour Minute | SpecificTime Hour Minute
deriving (Eq, Read, Show, Ord) deriving (Eq, Read, Show, Ord)
type Hour = Int type Hour = Int
type Minute = Int type Minute = Int
@ -73,7 +73,7 @@ type Minute = Int
data NextTime data NextTime
= NextTimeExactly LocalTime = NextTimeExactly LocalTime
| NextTimeWindow LocalTime LocalTime | NextTimeWindow LocalTime LocalTime
deriving (Eq, Read, Show) deriving (Eq, Read, Show)
startTime :: NextTime -> LocalTime startTime :: NextTime -> LocalTime
startTime (NextTimeExactly t) = t startTime (NextTimeExactly t) = t
@ -96,9 +96,9 @@ calcNextTime schedule@(Schedule recurrance scheduledtime) lasttime currenttime
NextTimeExactly t -> window (localDay t) (localDay t) NextTimeExactly t -> window (localDay t) (localDay t)
| otherwise = NextTimeExactly . startTime <$> findfromtoday False | otherwise = NextTimeExactly . startTime <$> findfromtoday False
where where
findfromtoday anytime = findfrom recurrance afterday today findfromtoday anytime = findfrom recurrance afterday today
where where
today = localDay currenttime today = localDay currenttime
afterday = sameaslastrun || toolatetoday afterday = sameaslastrun || toolatetoday
toolatetoday = not anytime && localTimeOfDay currenttime >= nexttime toolatetoday = not anytime && localTimeOfDay currenttime >= nexttime
sameaslastrun = lastrun == Just today sameaslastrun = lastrun == Just today
@ -163,8 +163,8 @@ calcNextTime schedule@(Schedule recurrance scheduledtime) lasttime currenttime
Divisible n r'@(Yearly _) -> handlediv n r' ynum Nothing Divisible n r'@(Yearly _) -> handlediv n r' ynum Nothing
Divisible _ r'@(Divisible _ _) -> findfrom r' afterday candidate Divisible _ r'@(Divisible _ _) -> findfrom r' afterday candidate
where where
skip n = findfrom r False (addDays n candidate) skip n = findfrom r False (addDays n candidate)
handlediv n r' getval mmax handlediv n r' getval mmax
| n > 0 && maybe True (n <=) mmax = | n > 0 && maybe True (n <=) mmax =
findfromwhere r' (divisible n . getval) afterday candidate findfromwhere r' (divisible n . getval) afterday candidate
| otherwise = Nothing | otherwise = Nothing
@ -267,7 +267,7 @@ toRecurrance s = case words s of
constructor u constructor u
| "s" `isSuffixOf` u = constructor $ reverse $ drop 1 $ reverse u | "s" `isSuffixOf` u = constructor $ reverse $ drop 1 $ reverse u
| otherwise = Nothing | otherwise = Nothing
withday sd u = do withday sd u = do
c <- constructor u c <- constructor u
d <- readish sd d <- readish sd
Just $ c (Just d) Just $ c (Just d)
@ -285,7 +285,7 @@ fromScheduledTime AnyTime = "any time"
fromScheduledTime (SpecificTime h m) = fromScheduledTime (SpecificTime h m) =
show h' ++ (if m > 0 then ":" ++ pad 2 (show m) else "") ++ " " ++ ampm show h' ++ (if m > 0 then ":" ++ pad 2 (show m) else "") ++ " " ++ ampm
where where
pad n s = take (n - length s) (repeat '0') ++ s pad n s = take (n - length s) (repeat '0') ++ s
(h', ampm) (h', ampm)
| h == 0 = (12, "AM") | h == 0 = (12, "AM")
| h < 12 = (h, "AM") | h < 12 = (h, "AM")
@ -304,10 +304,10 @@ toScheduledTime v = case words v of
(s:[]) -> go s id (s:[]) -> go s id
_ -> Nothing _ -> Nothing
where where
h0 h h0 h
| h == 12 = 0 | h == 12 = 0
| otherwise = h | otherwise = h
go :: String -> (Int -> Int) -> Maybe ScheduledTime go :: String -> (Int -> Int) -> Maybe ScheduledTime
go s adjust = go s adjust =
let (h, m) = separate (== ':') s let (h, m) = separate (== ':') s
in SpecificTime in SpecificTime
@ -363,7 +363,7 @@ instance Arbitrary Recurrance where
] ]
] ]
where where
arbday = oneof arbday = oneof
[ Just <$> nonNegative arbitrary [ Just <$> nonNegative arbitrary
, pure Nothing , pure Nothing
] ]

View File

@ -1,6 +1,6 @@
{- thread scheduling {- thread scheduling
- -
- Copyright 2012, 2013 Joey Hess <id@joeyh.name> - Copyright 2012, 2013 Joey Hess <joey@kitenet.net>
- Copyright 2011 Bas van Dijk & Roel van Dijk - Copyright 2011 Bas van Dijk & Roel van Dijk
- -
- License: BSD-2-clause - License: BSD-2-clause
@ -57,8 +57,7 @@ unboundDelay time = do
waitForTermination :: IO () waitForTermination :: IO ()
waitForTermination = do waitForTermination = do
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS
runEvery (Seconds 600) $ forever $ threadDelaySeconds (Seconds 6000)
void getLine
#else #else
lock <- newEmptyMVar lock <- newEmptyMVar
let check sig = void $ let check sig = void $

View File

@ -1,6 +1,6 @@
{- user info {- user info
- -
- Copyright 2012 Joey Hess <id@joeyh.name> - Copyright 2012 Joey Hess <joey@kitenet.net>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
@ -13,8 +13,10 @@ module Utility.UserInfo (
myUserGecos, myUserGecos,
) where ) where
import Control.Applicative
import System.PosixCompat import System.PosixCompat
#ifndef mingw32_HOST_OS
import Control.Applicative
#endif
import Utility.Env import Utility.Env
@ -40,16 +42,20 @@ myUserName = myVal env userName
env = ["USERNAME", "USER", "LOGNAME"] env = ["USERNAME", "USER", "LOGNAME"]
#endif #endif
myUserGecos :: IO String myUserGecos :: IO (Maybe String)
#ifdef __ANDROID__ -- userGecos crashes on Android and is not available on Windows.
myUserGecos = return "" -- userGecos crashes on Android #if defined(__ANDROID__) || defined(mingw32_HOST_OS)
myUserGecos = return Nothing
#else #else
myUserGecos = myVal [] userGecos myUserGecos = Just <$> myVal [] userGecos
#endif #endif
myVal :: [String] -> (UserEntry -> String) -> IO String myVal :: [String] -> (UserEntry -> String) -> IO String
myVal envvars extract = maybe (extract <$> getpwent) return =<< check envvars myVal envvars extract = go envvars
where where
check [] = return Nothing #ifndef mingw32_HOST_OS
check (v:vs) = maybe (check vs) (return . Just) =<< getEnv v go [] = extract <$> (getUserEntryForID =<< getEffectiveUserID)
getpwent = getUserEntryForID =<< getEffectiveUserID #else
go [] = error $ "environment not set: " ++ show envvars
#endif
go (v:vs) = maybe (go vs) return =<< getEnv v