Skip to content

Commit 1bfa2d4

Browse files
habibalaminjuanpaucar
authored andcommitted
Expand existing variables (#42)
* Allow parsing of interpolation in variables. * Extract ParsedVariable type to new file. * Interpolate references to previous variables / environment. * Fix nested many parser error. * Derive Show instances for ParsedVariable types. * Update tests to use ParsedVariable. * Add tests for interpolation and variable referencing. * Split long spec lines. * Add (<$>) imports for old versions of GHC. * Split long import line in ParseSpec. * Only import <$> in ParseSpec if necessary. * Add ParsedVariable to cabal file. * Change variable types prefix V -> Var. * Only import (<$>) for test if necessary.
1 parent 8926195 commit 1bfa2d4

File tree

7 files changed

+180
-31
lines changed

7 files changed

+180
-31
lines changed

dotenv.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ executable dotenv
7070
library
7171
exposed-modules: Configuration.Dotenv
7272
, Configuration.Dotenv.Parse
73+
, Configuration.Dotenv.ParsedVariable
7374
, Configuration.Dotenv.Text
7475

7576
build-depends: base >=4.6 && <5.0
@@ -97,6 +98,7 @@ test-suite dotenv-test
9798
, Configuration.Dotenv
9899
, Configuration.Dotenv.Text
99100
, Configuration.Dotenv.Parse
101+
, Configuration.Dotenv.ParsedVariable
100102

101103
build-depends: base >=4.6 && <5.0
102104
, base-compat >= 0.4

spec/Configuration/Dotenv/ParseSpec.hs

Lines changed: 77 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,9 @@
33
module Configuration.Dotenv.ParseSpec (main, spec) where
44

55
import Configuration.Dotenv.Parse (configParser)
6+
import Configuration.Dotenv.ParsedVariable (ParsedVariable(..),
7+
VarValue(..),
8+
VarFragment(..))
69
import Test.Hspec (it, describe, Spec, hspec)
710
import Test.Hspec.Megaparsec (shouldParse, shouldFailOn)
811
import Text.Megaparsec (ParseError, Dec, parse)
@@ -13,76 +16,130 @@ main = hspec spec
1316
spec :: Spec
1417
spec = describe "parse" $ do
1518
it "parses unquoted values" $
16-
parseConfig "FOO=bar" `shouldParse` [("FOO", "bar")]
19+
parseConfig "FOO=bar"
20+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "bar"])]
1721

1822
it "parses values with spaces around equal signs" $ do
19-
parseConfig "FOO =bar" `shouldParse` [("FOO", "bar")]
20-
parseConfig "FOO= bar" `shouldParse` [("FOO", "bar")]
21-
parseConfig "FOO =\t bar" `shouldParse` [("FOO", "bar")]
23+
parseConfig "FOO =bar"
24+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "bar"])]
25+
parseConfig "FOO= bar"
26+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "bar"])]
27+
parseConfig "FOO =\t bar"
28+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "bar"])]
2229

2330
it "parses double-quoted values" $
24-
parseConfig "FOO=\"bar\"" `shouldParse` [("FOO", "bar")]
31+
parseConfig "FOO=\"bar\""
32+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarLiteral "bar"])]
2533

2634
it "parses single-quoted values" $
27-
parseConfig "FOO='bar'" `shouldParse` [("FOO", "bar")]
35+
parseConfig "FOO='bar'"
36+
`shouldParse` [ParsedVariable "FOO" (SingleQuoted [VarLiteral "bar"])]
2837

2938
it "parses escaped double quotes" $
3039
parseConfig "FOO=\"escaped\\\"bar\""
31-
`shouldParse` [("FOO", "escaped\"bar")]
40+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarLiteral "escaped\"bar"])]
3241

3342
it "supports CRLF line breaks" $
3443
parseConfig "FOO=bar\r\nbaz=fbb"
35-
`shouldParse` [("FOO", "bar"), ("baz", "fbb")]
44+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "bar"]),
45+
ParsedVariable "baz" (Unquoted [VarLiteral "fbb"])]
3646

3747
it "parses empty values" $
38-
parseConfig "FOO=" `shouldParse` [("FOO", "")]
48+
parseConfig "FOO="
49+
`shouldParse` [ParsedVariable "FOO" (Unquoted [])]
50+
51+
it "parses unquoted interpolated values" $ do
52+
parseConfig "FOO=$HOME"
53+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarInterpolation "HOME"])]
54+
parseConfig "FOO=abc_$HOME"
55+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "abc_",
56+
VarInterpolation "HOME"])
57+
]
58+
parseConfig "FOO=${HOME}"
59+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarInterpolation "HOME"])]
60+
parseConfig "FOO=abc_${HOME}"
61+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "abc_",
62+
VarInterpolation "HOME"])
63+
]
64+
65+
it "parses double-quoted interpolated values" $ do
66+
parseConfig "FOO=\"$HOME\""
67+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarInterpolation "HOME"])]
68+
parseConfig "FOO=\"abc_$HOME\""
69+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarLiteral "abc_",
70+
VarInterpolation "HOME"])
71+
]
72+
parseConfig "FOO=\"${HOME}\""
73+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarInterpolation "HOME"])]
74+
parseConfig "FOO=\"abc_${HOME}\""
75+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarLiteral "abc_",
76+
VarInterpolation "HOME"])
77+
]
78+
79+
it "parses single-quoted interpolated values as literals" $ do
80+
parseConfig "FOO='$HOME'"
81+
`shouldParse` [ParsedVariable "FOO" (SingleQuoted [VarLiteral "$HOME"])]
82+
parseConfig "FOO='abc_$HOME'"
83+
`shouldParse` [ParsedVariable "FOO" (SingleQuoted [VarLiteral "abc_$HOME"])]
84+
parseConfig "FOO='${HOME}'"
85+
`shouldParse` [ParsedVariable "FOO" (SingleQuoted [VarLiteral "${HOME}"])]
86+
parseConfig "FOO='abc_${HOME}'"
87+
`shouldParse` [ParsedVariable "FOO" (SingleQuoted [VarLiteral "abc_${HOME}"])]
3988

4089
it "does not parse if line format is incorrect" $ do
4190
parseConfig `shouldFailOn` "lol$wut"
4291
parseConfig `shouldFailOn` "KEY=\nVALUE"
4392
parseConfig `shouldFailOn` "KEY\n=VALUE"
4493

4594
it "expands newlines in quoted strings" $
46-
parseConfig "FOO=\"bar\nbaz\"" `shouldParse` [("FOO", "bar\nbaz")]
95+
parseConfig "FOO=\"bar\nbaz\""
96+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarLiteral "bar\nbaz"])]
4797

4898
it "does not parse variables with hyphens in the name" $
4999
parseConfig `shouldFailOn` "FOO-BAR=foobar"
50100

51101
it "parses variables with \"_\" in the name" $
52-
parseConfig "FOO_BAR=foobar" `shouldParse` [("FOO_BAR", "foobar")]
102+
parseConfig "FOO_BAR=foobar"
103+
`shouldParse` [ParsedVariable "FOO_BAR" (Unquoted [VarLiteral "foobar"])]
53104

54105
it "parses variables with digits after the first character" $
55-
parseConfig "FOO_BAR_12=foobar" `shouldParse` [("FOO_BAR_12", "foobar")]
106+
parseConfig "FOO_BAR_12=foobar"
107+
`shouldParse` [ParsedVariable "FOO_BAR_12" (Unquoted [VarLiteral "foobar"])]
56108

57109
it "allows vertical spaces after a quoted variable" $
58-
parseConfig "foo='bar' " `shouldParse` [("foo", "bar")]
110+
parseConfig "foo='bar' "
111+
`shouldParse` [ParsedVariable "foo" (SingleQuoted [VarLiteral "bar"])]
59112

60113
it "does not parse variable names beginning with a digit" $
61114
parseConfig `shouldFailOn` "45FOO_BAR=foobar"
62115

63116
it "strips unquoted values" $
64-
parseConfig "foo=bar " `shouldParse` [("foo", "bar")]
117+
parseConfig "foo=bar "
118+
`shouldParse` [ParsedVariable "foo" (Unquoted [VarLiteral "bar"])]
65119

66120
it "ignores empty lines" $
67121
parseConfig "\n \t \nfoo=bar\n \nfizz=buzz"
68-
`shouldParse` [("foo", "bar"), ("fizz", "buzz")]
122+
`shouldParse` [ParsedVariable "foo" (Unquoted [VarLiteral "bar"]),
123+
ParsedVariable "fizz" (Unquoted [VarLiteral "buzz"])]
69124

70125
it "ignores inline comments after unquoted arguments" $
71-
parseConfig "FOO=bar # this is foo" `shouldParse` [("FOO", "bar")]
126+
parseConfig "FOO=bar # this is foo"
127+
`shouldParse` [ParsedVariable "FOO" (Unquoted [VarLiteral "bar"])]
72128

73129
it "ignores inline comments after quoted arguments" $
74-
parseConfig "FOO=\"bar\" # this is foo" `shouldParse` [("FOO", "bar")]
130+
parseConfig "FOO=\"bar\" # this is foo"
131+
`shouldParse` [ParsedVariable "FOO" (DoubleQuoted [VarLiteral "bar"])]
75132

76133
it "allows \"#\" in quoted values" $
77134
parseConfig "foo=\"bar#baz\" # comment"
78-
`shouldParse` [("foo", "bar#baz")]
135+
`shouldParse` [ParsedVariable "foo" (DoubleQuoted [VarLiteral "bar#baz"])]
79136

80137
it "ignores comment lines" $
81138
parseConfig "\n\t \n\n # HERE GOES FOO \nfoo=bar"
82-
`shouldParse` [("foo", "bar")]
139+
`shouldParse` [ParsedVariable "foo" (Unquoted [VarLiteral "bar"])]
83140

84141
it "doesn't allow more configuration options after a quoted value" $
85142
parseConfig `shouldFailOn` "foo='bar'baz='buz'"
86143

87-
parseConfig :: String -> Either (ParseError Char Dec) [(String, String)]
144+
parseConfig :: String -> Either (ParseError Char Dec) [ParsedVariable]
88145
parseConfig = parse configParser ""

spec/Configuration/DotenvSpec.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,10 @@ import Test.Hspec
88

99
import System.Environment (lookupEnv)
1010
import Control.Monad (liftM)
11+
import Data.Maybe (fromMaybe)
12+
#if !MIN_VERSION_base(4,8,0)
13+
import Data.Functor ((<$>))
14+
#endif
1115

1216
#if !MIN_VERSION_base(4,8,0)
1317
import Control.Applicative ((<$))
@@ -83,6 +87,15 @@ spec = do
8387
liftM (!! 1) (parseFile "spec/fixtures/.dotenv") `shouldReturn`
8488
("UNICODE_TEST", "Manabí")
8589

90+
it "recognises environment variables" $ do
91+
home <- fromMaybe "" <$> lookupEnv "HOME"
92+
liftM (!! 2) (parseFile "spec/fixtures/.dotenv") `shouldReturn`
93+
("ENVIRONMENT", home)
94+
95+
it "recognises previous variables" $
96+
liftM (!! 3) (parseFile "spec/fixtures/.dotenv") `shouldReturn`
97+
("PREVIOUS", "true")
98+
8699
describe "onMissingFile" $ after_ (unsetEnv "DOTENV") $ do
87100
context "when target file is present" $
88101
it "loading works as usual" $ do

spec/fixtures/.dotenv

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,4 @@
11
DOTENV=true
22
UNICODE_TEST=Manabí
3+
ENVIRONMENT="$HOME"
4+
PREVIOUS="$DOTENV"

src/Configuration/Dotenv.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module Configuration.Dotenv
1919
where
2020

2121
import Configuration.Dotenv.Parse (configParser)
22+
import Configuration.Dotenv.ParsedVariable (interpolateParsedVariables)
2223
import Control.Monad.Catch
2324
import Control.Monad.IO.Class (MonadIO(..))
2425
import System.Environment (lookupEnv)
@@ -60,7 +61,7 @@ parseFile f = do
6061

6162
case parse configParser f contents of
6263
Left e -> error $ "Failed to read file" ++ show e
63-
Right options -> return options
64+
Right options -> liftIO $ interpolateParsedVariables options
6465

6566
applySetting :: MonadIO m => Bool -> (String, String) -> m ()
6667
applySetting override (key, value) =

src/Configuration/Dotenv/Parse.hs

Lines changed: 27 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -16,43 +16,60 @@
1616

1717
module Configuration.Dotenv.Parse (configParser) where
1818

19+
import Configuration.Dotenv.ParsedVariable
1920
import Control.Applicative
2021
import Control.Monad
2122
import Text.Megaparsec
2223
import Text.Megaparsec.String (Parser)
2324
import qualified Text.Megaparsec.Lexer as L
2425

26+
data QuoteType = SingleQuote | DoubleQuote
27+
2528
-- | Returns a parser for a Dotenv configuration file. Accepts key and value
2629
-- arguments separated by @=@. Comments in all positions are handled
2730
-- appropriately.
28-
configParser :: Parser [(String, String)]
31+
configParser :: Parser [ParsedVariable]
2932
configParser = between scn eof (sepEndBy1 envLine (eol <* scn))
3033

3134
-- | Parse a single environment variable assignment.
32-
envLine :: Parser (String, String)
33-
envLine = (,) <$> (lexeme variableName <* lexeme (char '=')) <*> lexeme value
35+
envLine :: Parser ParsedVariable
36+
envLine = ParsedVariable <$> (lexeme variableName <* lexeme (char '=')) <*> lexeme value
3437

3538
-- | Variables must start with a letter or underscore, and may contain
3639
-- letters, digits or '_' character after the first character.
37-
variableName :: Parser String
40+
variableName :: Parser VarName
3841
variableName = ((:) <$> firstChar <*> many otherChar) <?> "variable name"
3942
where
4043
firstChar = char '_' <|> letterChar
4144
otherChar = firstChar <|> digitChar
4245

4346
-- | Value: quoted or unquoted.
44-
value :: Parser String
47+
value :: Parser VarValue
4548
value = (quotedValue <|> unquotedValue) <?> "variable value"
4649
where
47-
quotedValue = quotedWith '\'' <|> quotedWith '\"'
48-
unquotedValue = many (noneOf "\'\" \t\n\r")
50+
quotedValue = quotedWith SingleQuote <|> quotedWith DoubleQuote
51+
unquotedValue = Unquoted <$> (many $ fragment "\'\" \t\n\r")
4952

5053
-- | Parse a value quoted with given character.
51-
quotedWith :: Char -> Parser String
52-
quotedWith q = between (char q) (char q) (many $ escapedChar <|> normalChar)
54+
quotedWith :: QuoteType -> Parser VarValue
55+
quotedWith SingleQuote = SingleQuoted <$> (between (char '\'') (char '\'') $ many (literalValueFragment "\'\\"))
56+
quotedWith DoubleQuote = DoubleQuoted <$> (between (char '\"') (char '\"') $ many (fragment "\""))
57+
58+
fragment :: [Char] -> Parser VarFragment
59+
fragment charsToEscape = interpolatedValueFragment <|> literalValueFragment ('$' : '\\' : charsToEscape)
60+
61+
interpolatedValueFragment :: Parser VarFragment
62+
interpolatedValueFragment = VarInterpolation <$>
63+
((between (symbol "${") (symbol "}") variableName) <|>
64+
(char '$' >> variableName))
65+
where
66+
symbol = L.symbol sc
67+
68+
literalValueFragment :: [Char] -> Parser VarFragment
69+
literalValueFragment charsToEscape = VarLiteral <$> (some $ escapedChar <|> normalChar)
5370
where
5471
escapedChar = (char '\\' *> anyChar) <?> "escaped character"
55-
normalChar = noneOf (q : "\\") <?> "unescaped character"
72+
normalChar = noneOf charsToEscape <?> "unescaped character"
5673

5774
----------------------------------------------------------------------------
5875
-- Boilerplate and whitespace setup
Lines changed: 57 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,57 @@
1+
{-# LANGUAGE CPP #-}
2+
3+
module Configuration.Dotenv.ParsedVariable (ParsedVariable(..),
4+
VarName,
5+
VarValue(..),
6+
VarContents,
7+
VarFragment(..),
8+
interpolateParsedVariables) where
9+
10+
import Control.Monad (foldM)
11+
#if !MIN_VERSION_base(4,8,0)
12+
import Data.Functor ((<$>))
13+
#endif
14+
import Control.Applicative ((<|>))
15+
import System.Environment (lookupEnv)
16+
17+
data ParsedVariable
18+
= ParsedVariable VarName VarValue deriving (Show, Eq)
19+
20+
type VarName = String
21+
22+
data VarValue
23+
= Unquoted VarContents
24+
| SingleQuoted VarContents
25+
| DoubleQuoted VarContents deriving (Show, Eq)
26+
27+
type VarContents = [VarFragment]
28+
29+
data VarFragment
30+
= VarInterpolation String
31+
| VarLiteral String deriving (Show, Eq)
32+
33+
interpolateParsedVariables :: [ParsedVariable] -> IO [(String, String)]
34+
interpolateParsedVariables = fmap reverse . foldM addInterpolated []
35+
36+
addInterpolated :: [(String, String)] -> ParsedVariable -> IO [(String, String)]
37+
addInterpolated previous (ParsedVariable name value) = (: previous) <$> ((,) name <$> interpolate previous value)
38+
39+
interpolate :: [(String, String)] -> VarValue -> IO String
40+
interpolate _ (SingleQuoted contents) = return $ joinContents contents
41+
interpolate previous (DoubleQuoted contents) = interpolateContents previous contents
42+
interpolate previous (Unquoted contents) = interpolateContents previous contents
43+
44+
interpolateContents :: [(String, String)] -> VarContents -> IO String
45+
interpolateContents previous contents = concat <$> mapM (interpolateFragment previous) contents
46+
47+
interpolateFragment :: [(String, String)] -> VarFragment -> IO String
48+
interpolateFragment _ (VarLiteral value ) = return value
49+
interpolateFragment previous (VarInterpolation varname) = fromPreviousOrEnv >>= maybe (return "") return
50+
where
51+
fromPreviousOrEnv = (lookup varname previous <|>) <$> lookupEnv varname
52+
53+
joinContents :: VarContents -> String
54+
joinContents = concatMap fragmentToString
55+
where
56+
fragmentToString (VarInterpolation value) = value
57+
fragmentToString (VarLiteral value) = value

0 commit comments

Comments
 (0)