{-# LANGUAGE Safe #-}

{- |
Module                  : Relude.Lifted.Env
Copyright               : (c) 2020-2022 Kowainik
SPDX-License-Identifier : MIT
Maintainer              : Kowainik <xrom.xkov@gmail.com>
Stability               : Stable
Portability             : Portable

Lifted functions to work with system environment.

@since 1.0.0.0
-}

module Relude.Lifted.Env
    ( getArgs
    , lookupEnv
    ) where

import Relude.Base (IO)
import Relude.Function ((.))
import Relude.Monad.Reexport (MonadIO (..), Maybe)
import Relude.String.Reexport (String)

import qualified System.Environment as ENV (getArgs, lookupEnv)

{- | Lifted version of 'System.Environment.getArgs'.

@since 1.0.0.0
-}
getArgs :: MonadIO m => m [String]
getArgs :: m [String]
getArgs = IO [String] -> m [String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [String]
ENV.getArgs
{-# SPECIALIZE getArgs :: IO [String] #-}
{-# INLINE getArgs #-}

{- | Lifted version of 'System.Environment.lookupEnv'.

@since 1.0.0.0
-}
lookupEnv :: MonadIO m => String -> m (Maybe String)
lookupEnv :: String -> m (Maybe String)
lookupEnv = IO (Maybe String) -> m (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> m (Maybe String))
-> (String -> IO (Maybe String)) -> String -> m (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO (Maybe String)
ENV.lookupEnv
{-# SPECIALIZE lookupEnv :: String -> IO (Maybe String) #-}
{-# INLINE lookupEnv #-}