{- OSX stuff - - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} module Utility.OSX where import Utility.UserInfo import System.FilePath autoStartBase :: String -> FilePath autoStartBase label = "Library" "LaunchAgents" label ++ ".plist" systemAutoStart :: String -> FilePath systemAutoStart label = "/" autoStartBase label userAutoStart :: String -> IO FilePath userAutoStart label = do home <- myHomeDir return $ home autoStartBase label {- Generates an OSX autostart plist file with a given label, command, and - params to run at boot or login. -} genOSXAutoStartFile :: String -> String -> [String] -> String genOSXAutoStartFile label command params = unlines [ "" , "" , "" , "" , "Label" , "" ++ label ++ "" , "ProgramArguments" , "" , unlines $ map (\v -> "" ++ v ++ "") (command:params) , "" , "RunAtLoad" , "" , "" , "" ]