{- Environment variables functions. Copyright (C) 2005, 2008 Luis Francisco Araujo -} module Environment where import System.Posix.Env (getEnv, putEnv) import Text.Regex (mkRegex, splitRegex) data Alias = Alias { command , newcommand :: String } deriving (Show, Eq) type Prompt = String type FileOpts = [(String, String)] type ExecutionEnv = (Prompt , [Alias]) {- | Setup and get specific values from environment variables. -} ---------------------------------------------------------------------------------- -- | Setup all the enviromment variables specified in the configuration file. getVariables :: FileOpts -> IO () getVariables xs = mapM_ (\ (a , b) -> putEnv (a ++ "=" ++ b)) xs -- | Setup environment variables. setEnvVar :: IO ExecutionEnv setEnvVar = do prompt <- getShellPrompt lalias <- getAlias return (prompt, lalias) ---------------------------------------------------------------------------------- -- | PROMPT variable. getShellPrompt :: IO String getShellPrompt = do sp <- getEnv "PROMPT" case sp of Nothing -> return [] Just a -> return a ---------------------------------------------------------------------------------- -- | ALIAS variable. getAlias :: IO [Alias] getAlias = do v <- getEnv "ALIAS" alias <- case v of{ Nothing -> return [] ; Just a -> return a } return $ map (\ s -> Alias { command = s !! 0, newcommand = s !! 1 }) (aliaslist alias) where aliaslist = map (splitRegex (mkRegex ":")) . splitRegex (mkRegex "\\|") ---------------------------------------------------------------------------------- -- | Get the value of any variable. getEnvVariable :: String -> IO String getEnvVariable v = do env <- getEnv v case env of Nothing -> return [] Just n -> return n