-- |
-- Module      :  Configuration.Dotenv.Types
-- Copyright   :  © 2015–2020 Stack Builders Inc.
-- License     :  MIT
--
-- Maintainer  :  Stack Builders <hackage@stackbuilders.com>
-- Stability   :  experimental
-- Portability :  portable
--
-- This module contains common functions to load and read dotenv files.
{-# LANGUAGE RecordWildCards #-}

module Configuration.Dotenv
  ( -- * Dotenv Load Functions
    load
  , loadFile
  , parseFile
  , onMissingFile
      -- * Dotenv Types
  , module Configuration.Dotenv.Types
  ) where

import           Configuration.Dotenv.Environment    (getEnvironment, lookupEnv,
                                                      setEnv)
import           Configuration.Dotenv.Parse          (configParser)
import           Configuration.Dotenv.ParsedVariable (interpolateParsedVariables)
import           Configuration.Dotenv.Types          (Config (..), ReaderT, ask,
                                                      defaultConfig,
                                                      liftReaderT, runReaderT)
import           Control.Exception                   (throw)
import           Control.Monad                       (when)
import           Control.Monad.Catch
import           Control.Monad.Compat                (unless)
import           Control.Monad.IO.Class              (MonadIO (..))
import           Data.List                           (intersectBy, union,
                                                      unionBy)
import           System.IO.Error                     (isDoesNotExistError)
import           Text.Megaparsec                     (errorBundlePretty, parse)

-- | Monad Stack for the application
type DotEnv m a = ReaderT Config m a

-- | Loads the given list of options into the environment. Optionally
-- override existing variables with values from Dotenv files.
load ::
     MonadIO m
  => Bool -- ^ Override existing settings?
  -> [(String, String)] -- ^ List of values to be set in environment
  -> m ()
load :: Bool -> [(String, String)] -> m ()
load Bool
override [(String, String)]
kv =
  ReaderT Config m () -> Config -> m ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (((String, String) -> ReaderT Config m (String, String))
-> [(String, String)] -> ReaderT Config m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String, String) -> ReaderT Config m (String, String)
forall (m :: * -> *).
MonadIO m =>
(String, String) -> DotEnv m (String, String)
applySetting [(String, String)]
kv) Config
defaultConfig {configOverride :: Bool
configOverride = Bool
override}

-- | @loadFile@ parses the environment variables defined in the dotenv example
-- file and checks if they are defined in the dotenv file or in the environment.
-- It also allows to override the environment variables defined in the environment
-- with the values defined in the dotenv file.
loadFile ::
     MonadIO m
  => Config -- ^ Dotenv configuration
  -> m ()
loadFile :: Config -> m ()
loadFile config :: Config
config@Config {Bool
[String]
allowDuplicates :: Config -> Bool
configVerbose :: Config -> Bool
configExamplePath :: Config -> [String]
configPath :: Config -> [String]
allowDuplicates :: Bool
configVerbose :: Bool
configOverride :: Bool
configExamplePath :: [String]
configPath :: [String]
configOverride :: Config -> Bool
..} = do
  [(String, String)]
environment <- IO [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getEnvironment
  [(String, String)]
readVars <- ([[(String, String)]] -> [(String, String)])
-> m [[(String, String)]] -> m [(String, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[(String, String)]] -> [(String, String)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((String -> m [(String, String)])
-> [String] -> m [[(String, String)]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> m [(String, String)]
forall (m :: * -> *). MonadIO m => String -> m [(String, String)]
parseFile [String]
configPath)
  [(String, String)]
neededVars <- ([[(String, String)]] -> [(String, String)])
-> m [[(String, String)]] -> m [(String, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[(String, String)]] -> [(String, String)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((String -> m [(String, String)])
-> [String] -> m [[(String, String)]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> m [(String, String)]
forall (m :: * -> *). MonadIO m => String -> m [(String, String)]
parseFile [String]
configExamplePath)
  let coincidences :: [(String, String)]
coincidences = ([(String, String)]
environment [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. Eq a => [a] -> [a] -> [a]
`union` [(String, String)]
readVars) [(String, String)] -> [(String, String)] -> [(String, String)]
forall b. [(String, b)] -> [(String, b)] -> [(String, b)]
`intersectEnvs` [(String, String)]
neededVars
      cmpEnvs :: (a, b) -> (a, b) -> Bool
cmpEnvs (a, b)
env1 (a, b)
env2 = (a, b) -> a
forall a b. (a, b) -> a
fst (a, b)
env1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== (a, b) -> a
forall a b. (a, b) -> a
fst (a, b)
env2
      intersectEnvs :: [(String, b)] -> [(String, b)] -> [(String, b)]
intersectEnvs = ((String, b) -> (String, b) -> Bool)
-> [(String, b)] -> [(String, b)] -> [(String, b)]
forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]
intersectBy (String, b) -> (String, b) -> Bool
forall a b b. Eq a => (a, b) -> (a, b) -> Bool
cmpEnvs
      unionEnvs :: [(String, b)] -> [(String, b)] -> [(String, b)]
unionEnvs = ((String, b) -> (String, b) -> Bool)
-> [(String, b)] -> [(String, b)] -> [(String, b)]
forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]
unionBy (String, b) -> (String, b) -> Bool
forall a b b. Eq a => (a, b) -> (a, b) -> Bool
cmpEnvs
      vars :: [(String, String)]
vars =
        if (Bool -> Bool
not (Bool -> Bool)
-> ([(String, String)] -> Bool) -> [(String, String)] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(String, String)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [(String, String)]
neededVars
          then if [(String, String)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(String, String)]
neededVars Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [(String, String)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(String, String)]
coincidences
                 then [(String, String)]
readVars [(String, String)] -> [(String, String)] -> [(String, String)]
forall b. [(String, b)] -> [(String, b)] -> [(String, b)]
`unionEnvs` [(String, String)]
neededVars
                 else String -> [(String, String)]
forall a. HasCallStack => String -> a
error (String -> [(String, String)]) -> String -> [(String, String)]
forall a b. (a -> b) -> a -> b
$
                      String
"Missing env vars! Please, check (this/these) var(s) (is/are) set:" String -> String -> String
forall a. [a] -> [a] -> [a]
++
                      ((String, String) -> String) -> [(String, String)] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String -> String -> String
forall a. [a] -> [a] -> [a]
(++) String
" " (String -> String)
-> ((String, String) -> String) -> (String, String) -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, String) -> String
forall a b. (a, b) -> a
fst) [(String, String)]
neededVars
          else [(String, String)]
readVars
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
allowDuplicates (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ ([String] -> m ()
forall (m :: * -> *). MonadIO m => [String] -> m ()
lookUpDuplicates ([String] -> m ())
-> ([(String, String)] -> [String]) -> [(String, String)] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, String) -> String) -> [(String, String)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> String
forall a b. (a, b) -> a
fst) [(String, String)]
vars
  ReaderT Config m () -> Config -> m ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (((String, String) -> ReaderT Config m (String, String))
-> [(String, String)] -> ReaderT Config m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String, String) -> ReaderT Config m (String, String)
forall (m :: * -> *).
MonadIO m =>
(String, String) -> DotEnv m (String, String)
applySetting [(String, String)]
vars) Config
config

-- | Parses the given dotenv file and returns values /without/ adding them to
-- the environment.
parseFile ::
     MonadIO m
  => FilePath -- ^ A file containing options to read
  -> m [(String, String)] -- ^ Variables contained in the file
parseFile :: String -> m [(String, String)]
parseFile String
f = do
  String
contents <- IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ String -> IO String
readFile String
f
  case Parsec Void String [ParsedVariable]
-> String
-> String
-> Either (ParseErrorBundle String Void) [ParsedVariable]
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
parse Parsec Void String [ParsedVariable]
configParser String
f String
contents of
    Left ParseErrorBundle String Void
e        -> String -> m [(String, String)]
forall a. HasCallStack => String -> a
error (String -> m [(String, String)]) -> String -> m [(String, String)]
forall a b. (a -> b) -> a -> b
$ ParseErrorBundle String Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseErrorBundle String Void
e
    Right [ParsedVariable]
options -> IO [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(String, String)] -> m [(String, String)])
-> IO [(String, String)] -> m [(String, String)]
forall a b. (a -> b) -> a -> b
$ [ParsedVariable] -> IO [(String, String)]
interpolateParsedVariables [ParsedVariable]
options

applySetting ::
     MonadIO m
  => (String, String) -- ^ A key-value pair to set in the environment
  -> DotEnv m (String, String)
applySetting :: (String, String) -> DotEnv m (String, String)
applySetting kv :: (String, String)
kv@(String
k, String
v) = do
  Config {Bool
[String]
allowDuplicates :: Bool
configVerbose :: Bool
configOverride :: Bool
configExamplePath :: [String]
configPath :: [String]
allowDuplicates :: Config -> Bool
configVerbose :: Config -> Bool
configExamplePath :: Config -> [String]
configPath :: Config -> [String]
configOverride :: Config -> Bool
..} <- ReaderT Config m Config
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
  if Bool
configOverride
    then (String, String) -> DotEnv m ()
forall (m :: * -> *). MonadIO m => (String, String) -> DotEnv m ()
info (String, String)
kv DotEnv m ()
-> DotEnv m (String, String) -> DotEnv m (String, String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> DotEnv m (String, String)
forall r. ReaderT r m (String, String)
setEnv'
    else do
      Maybe String
res <- m (Maybe String) -> ReaderT Config m (Maybe String)
forall (m :: * -> *) a r. m a -> ReaderT r m a
liftReaderT (m (Maybe String) -> ReaderT Config m (Maybe String))
-> (IO (Maybe String) -> m (Maybe String))
-> IO (Maybe String)
-> ReaderT Config m (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Maybe String) -> m (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> ReaderT Config m (Maybe String))
-> IO (Maybe String) -> ReaderT Config m (Maybe String)
forall a b. (a -> b) -> a -> b
$ String -> IO (Maybe String)
lookupEnv String
k
      case Maybe String
res of
        Maybe String
Nothing -> (String, String) -> DotEnv m ()
forall (m :: * -> *). MonadIO m => (String, String) -> DotEnv m ()
info (String, String)
kv DotEnv m ()
-> DotEnv m (String, String) -> DotEnv m (String, String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> DotEnv m (String, String)
forall r. ReaderT r m (String, String)
setEnv'
        Just String
_  -> (String, String) -> DotEnv m (String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String, String)
kv
  where
    setEnv' :: ReaderT r m (String, String)
setEnv' = m (String, String) -> ReaderT r m (String, String)
forall (m :: * -> *) a r. m a -> ReaderT r m a
liftReaderT (m (String, String) -> ReaderT r m (String, String))
-> (IO (String, String) -> m (String, String))
-> IO (String, String)
-> ReaderT r m (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (String, String) -> m (String, String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (String, String) -> ReaderT r m (String, String))
-> IO (String, String) -> ReaderT r m (String, String)
forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
setEnv String
k String
v IO () -> IO (String, String) -> IO (String, String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (String, String) -> IO (String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String, String)
kv

-- | The function logs in console when a variable is loaded into the
-- environment.
info :: MonadIO m => (String, String) -> DotEnv m ()
info :: (String, String) -> DotEnv m ()
info (String
key, String
value) = do
  Config {Bool
[String]
allowDuplicates :: Bool
configVerbose :: Bool
configOverride :: Bool
configExamplePath :: [String]
configPath :: [String]
allowDuplicates :: Config -> Bool
configVerbose :: Config -> Bool
configExamplePath :: Config -> [String]
configPath :: Config -> [String]
configOverride :: Config -> Bool
..} <- ReaderT Config m Config
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
  Bool -> DotEnv m () -> DotEnv m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
configVerbose (DotEnv m () -> DotEnv m ()) -> DotEnv m () -> DotEnv m ()
forall a b. (a -> b) -> a -> b
$
    m () -> DotEnv m ()
forall (m :: * -> *) a r. m a -> ReaderT r m a
liftReaderT (m () -> DotEnv m ()) -> (IO () -> m ()) -> IO () -> DotEnv m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> DotEnv m ()) -> IO () -> DotEnv m ()
forall a b. (a -> b) -> a -> b
$
    String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"[INFO]: Load env '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
key String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' with value '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
value String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"

-- | The helper allows to avoid exceptions in the case of missing files and
-- perform some action instead.
--
-- @since 0.3.1.0
onMissingFile ::
     MonadCatch m
  => m a -- ^ Action to perform that may fail because of missing file
  -> m a -- ^ Action to perform if file is indeed missing
  -> m a
onMissingFile :: m a -> m a -> m a
onMissingFile m a
f m a
h = (IOError -> Bool) -> m a -> (IOError -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> Bool) -> m a -> (e -> m a) -> m a
catchIf IOError -> Bool
isDoesNotExistError m a
f (m a -> IOError -> m a
forall a b. a -> b -> a
const m a
h)

-- | The helper throws an exception if the allow duplicate is set to False.
forbidDuplicates :: MonadIO m => String -> m ()
forbidDuplicates :: String -> m ()
forbidDuplicates String
key =
  IOError -> m ()
forall a e. Exception e => e -> a
throw (IOError -> m ()) -> IOError -> m ()
forall a b. (a -> b) -> a -> b
$
  String -> IOError
userError (String -> IOError) -> String -> IOError
forall a b. (a -> b) -> a -> b
$
  String
"[ERROR]: Env '" String -> String -> String
forall a. [a] -> [a] -> [a]
++
  String
key String -> String -> String
forall a. [a] -> [a] -> [a]
++
  String
"' is duplicated in a dotenv file. Please, fix that (or remove --no-dups)."

lookUpDuplicates :: MonadIO m => [String] -> m ()
lookUpDuplicates :: [String] -> m ()
lookUpDuplicates [] = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
lookUpDuplicates [String
_] = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
lookUpDuplicates (String
x:[String]
xs) =
  if String
x String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
xs
    then String -> m ()
forall (m :: * -> *). MonadIO m => String -> m ()
forbidDuplicates String
x
    else [String] -> m ()
forall (m :: * -> *). MonadIO m => [String] -> m ()
lookUpDuplicates [String]
xs