Skip to content

Commit 4e4b671

Browse files
authored
New API uses variable name as record label. (#6)
1 parent ac37830 commit 4e4b671

File tree

7 files changed

+52
-72
lines changed

7 files changed

+52
-72
lines changed

examples/App.purs

Lines changed: 10 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module Example.App where
22

33
import Prelude
44

5-
import Control.Monad.Reader (ReaderT, asks, runReaderT)
5+
import Control.Monad.Reader (ReaderT, ask, asks, runReaderT)
66
import Control.Monad.Reader.Class (class MonadAsk)
77
import Data.Either (Either(..))
88
import Effect (Effect)
@@ -11,19 +11,17 @@ import Effect.Console (log)
1111
import Node.Process (getEnv)
1212
import Type.Equality (class TypeEquals, from)
1313
import Type.Proxy (Proxy(..))
14-
import TypedEnv (Resolved, Variable, envErrorMessage)
14+
import TypedEnv (envErrorMessage)
1515
import TypedEnv (fromEnv) as TypedEnv
1616

17-
type Config f =
18-
( alertEmail :: f "ALERT_EMAIL" String
19-
, alertSubject :: f "ALERT_SUBJECT" String
17+
type Config =
18+
( "ALERT_EMAIL" :: String
19+
, "ALERT_SUBJECT" :: String
2020
)
2121

22-
type ResolvedConfig = Record (Config Resolved)
22+
newtype AppM a = AppM (ReaderT { | Config } Effect a)
2323

24-
newtype AppM a = AppM (ReaderT ResolvedConfig Effect a)
25-
26-
runAppM :: ResolvedConfig -> AppM ~> Effect
24+
runAppM :: { | Config } -> AppM ~> Effect
2725
runAppM env (AppM m) = runReaderT m env
2826

2927
derive newtype instance functorAppM :: Functor AppM
@@ -33,12 +31,12 @@ derive newtype instance bindAppM :: Bind AppM
3331
derive newtype instance monadAppM :: Monad AppM
3432
derive newtype instance monadEffectAppM :: MonadEffect AppM
3533

36-
instance monadAskAppM :: TypeEquals e ResolvedConfig => MonadAsk e AppM where
34+
instance monadAskAppM :: TypeEquals e { | Config } => MonadAsk e AppM where
3735
ask = AppM $ asks from
3836

3937
main :: Effect Unit
4038
main = do
41-
eitherConfig <- TypedEnv.fromEnv (Proxy :: Proxy (Config Variable)) <$> getEnv
39+
eitherConfig <- TypedEnv.fromEnv (Proxy :: _ Config) <$> getEnv
4240
case eitherConfig of
4341
Left error ->
4442
log $ "ERROR: " <> envErrorMessage error
@@ -47,8 +45,7 @@ main = do
4745

4846
sendAlert :: AppM Unit
4947
sendAlert = do
50-
email <- asks _.alertEmail
51-
subject <- asks _.alertSubject
48+
{ "ALERT_EMAIL": email, "ALERT_SUBJECT": subject } <- ask
5249
liftEffect $ log
5350
( "Sending alert with subject \"" <> subject <> "\" to \"" <> email <>
5451
"\"...done."

examples/Basic.purs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,12 +8,12 @@ import Effect (Effect)
88
import Effect.Console (log)
99
import Node.Process (getEnv)
1010
import Type.Proxy (Proxy(..))
11-
import TypedEnv (type (<:), envErrorMessage)
11+
import TypedEnv (envErrorMessage)
1212
import TypedEnv (fromEnv) as TypedEnv
1313

1414
type Environment =
15-
( greeting :: String <: "GREETING"
16-
, count :: Int <: "COUNT"
15+
( "GREETING" :: String
16+
, "COUNT" :: Int
1717
)
1818

1919
main :: Effect Unit
@@ -22,6 +22,6 @@ main = do
2222
case env of
2323
Left error ->
2424
log $ "ERROR: " <> envErrorMessage error
25-
Right { greeting, count } -> do
25+
Right { "GREETING": greeting, "COUNT": count } -> do
2626
_ <- replicateM count (log greeting)
2727
pure unit

examples/CustomType.purs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Effect (Effect)
99
import Effect.Console (log)
1010
import Node.Process (getEnv)
1111
import Type.Proxy (Proxy(..))
12-
import TypedEnv (class ParseValue, type (<:), envErrorMessage)
12+
import TypedEnv (class ParseValue, envErrorMessage)
1313
import TypedEnv (fromEnv) as TypedEnv
1414

1515
newtype Port = Port Int
@@ -21,8 +21,8 @@ instance parseValuePort :: ParseValue Port where
2121
parseValue = map Port <<< find (_ <= 65535) <<< Int.fromString
2222

2323
type Settings =
24-
( host :: String <: "HOST"
25-
, port :: Port <: "PORT"
24+
( "HOST" :: String
25+
, "PORT" :: Port
2626
)
2727

2828
main :: Effect Unit
@@ -31,6 +31,6 @@ main = do
3131
case env of
3232
Left error ->
3333
log $ "ERROR: " <> envErrorMessage error
34-
Right { host, port } -> do
34+
Right { "HOST": host, "PORT": port } -> do
3535
log $ "Connected to " <> host <> ":" <> show port
36-
pure unit
36+
pure unit

examples/Optional.purs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,17 +8,17 @@ import Effect (Effect)
88
import Effect.Console (log)
99
import Node.Process (getEnv)
1010
import Type.Proxy (Proxy(..))
11-
import TypedEnv (type (<:), envErrorMessage)
11+
import TypedEnv (envErrorMessage)
1212
import TypedEnv (fromEnv) as TypedEnv
1313

14-
type Settings = (username :: Maybe String <: "USERNAME")
14+
type Settings = ("USERNAME" :: Maybe String)
1515

1616
main :: Effect Unit
1717
main = do
1818
env <- TypedEnv.fromEnv (Proxy :: Proxy Settings) <$> getEnv
1919
case env of
2020
Left error ->
2121
log $ "ERROR: " <> envErrorMessage error
22-
Right { username } -> do
22+
Right { "USERNAME": username } -> do
2323
log $ "Hello, " <> fromMaybe "Sailor" username <> "!"
2424
pure unit

examples/Reader.purs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -10,12 +10,12 @@ import Effect (Effect)
1010
import Effect.Console (log)
1111
import Node.Process (getEnv)
1212
import Type.Proxy (Proxy(..))
13-
import TypedEnv (type (<:), envErrorMessage)
13+
import TypedEnv (envErrorMessage)
1414
import TypedEnv (fromEnv) as TypedEnv
1515

1616
type Config =
17-
( username :: Maybe String <: "USERNAME"
18-
, repeat :: Maybe Int <: "REPEAT"
17+
( "USERNAME" :: Maybe String
18+
, "REPEAT" :: Maybe Int
1919
)
2020

2121
main :: Effect Unit
@@ -24,11 +24,11 @@ main = do
2424
case env of
2525
Left error ->
2626
log $ "ERROR: " <> envErrorMessage error
27-
Right config@{ repeat } -> do
27+
Right config@{ "REPEAT": repeat } -> do
2828
_ <- replicateM (1 + fromMaybe 0 repeat) $ log $ runReader greeting config
2929
pure unit
3030

31-
greeting :: forall r. Reader { username :: Maybe String | r } String
32-
greeting = asks _.username >>= \username -> pure $ "Hello, "
31+
greeting :: forall r. Reader { "USERNAME" :: Maybe String | r } String
32+
greeting = asks _."USERNAME" >>= \username -> pure $ "Hello, "
3333
<> fromMaybe "Sailor" username
34-
<> "!"
34+
<> "!"

src/TypedEnv.purs

Lines changed: 6 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -2,12 +2,8 @@
22

33
module TypedEnv
44
( fromEnv
5-
, Variable
6-
, VariableFlipped
7-
, type (<:)
85
, EnvError(..)
96
, envErrorMessage
10-
, Resolved
117
, class ParseValue
128
, parseValue
139
, class ReadValue
@@ -46,15 +42,6 @@ fromEnv
4642
-> Either EnvError (Record r)
4743
fromEnv = readEnv
4844

49-
-- | Specifies the name and type of an environment variable.
50-
data Variable (name :: Symbol) (ty :: Type)
51-
52-
-- | An alias for `Variable` with the parameters reversed
53-
type VariableFlipped ty name = Variable name ty
54-
55-
-- | An alias for `VariableFlipped`
56-
infixr 5 type VariableFlipped as <:
57-
5845
-- | An error that can occur while reading an environment variable
5946
data EnvError = EnvLookupError String | EnvParseError String
6047

@@ -73,10 +60,6 @@ envErrorMessage = case _ of
7360
EnvParseError var -> "The variable \"" <> var <>
7461
"\" was formatted incorrectly."
7562

76-
-- | Useful for a type alias representing a resolved environment
77-
type Resolved :: forall k. Symbol -> k -> k
78-
type Resolved (name :: Symbol) ty = ty
79-
8063
-- | Parses a `String` value to the specified type.
8164
class ParseValue ty where
8265
parseValue :: String -> Maybe ty
@@ -146,20 +129,20 @@ class
146129

147130
instance readEnvFieldsCons ::
148131
( IsSymbol name
149-
, IsSymbol varName
132+
, IsSymbol name
150133
, ListToRow rlt rt
151134
, ReadEnvFields elt rlt rt
152135
, Row.Lacks name rt
153136
, Row.Cons name ty rt r
154137
, ReadValue ty
155138
) =>
156-
ReadEnvFields (Cons name (Variable varName ty) elt) (Cons name ty rlt) r where
139+
ReadEnvFields (Cons name ty elt) (Cons name ty rlt) r where
157140
readEnvFields _ _ env = Record.insert nameP <$> value <*> tail
158141
where
159-
nameP = Proxy :: Proxy name
160-
varName = reflectSymbol (Proxy :: Proxy varName)
161-
value = readValue varName env
162-
tail = readEnvFields (Proxy :: Proxy elt) (Proxy :: Proxy rlt) env
142+
nameP = Proxy :: _ name
143+
name = reflectSymbol (Proxy :: _ name)
144+
value = readValue name env
145+
tail = readEnvFields (Proxy :: _ elt) (Proxy :: _ rlt) env
163146

164147
instance readEnvFieldsNil ::
165148
TypeEquals {} (Record row) =>

test/Main.purs

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ import Test.Spec.Assertions (shouldEqual)
1313
import Test.Spec.Reporter.Console (consoleReporter)
1414
import Test.Spec.Runner (runSpec)
1515
import Type.Proxy (Proxy(..))
16-
import TypedEnv (type (<:), EnvError(..), fromEnv)
16+
import TypedEnv (EnvError(..), fromEnv)
1717

1818
main :: Effect Unit
1919
main = launchAff_ $ runSpec [ consoleReporter ] $
@@ -23,33 +23,33 @@ main = launchAff_ $ runSpec [ consoleReporter ] $
2323
let
2424
env = FO.fromHomogeneous
2525
{ "A": "a value", "B": "b value", "C": "c value" }
26-
expected = Right { b: "b value", c: "c value" }
27-
actual = fromEnv (Proxy :: _ (b :: String <: "B", c :: String <: "C"))
26+
expected = Right { "B": "b value", "C": "c value" }
27+
actual = fromEnv (Proxy :: _ ("B" :: String, "C" :: String))
2828
env
2929
actual `shouldEqual` expected
3030

3131
it "indicates when a lookup has failed" do
3232
let
3333
env = FO.fromHomogeneous { "GREETING": "Hello" }
3434
expected = Left (EnvLookupError "MESSAGE")
35-
actual = fromEnv (Proxy :: _ (message :: String <: "MESSAGE")) env
35+
actual = fromEnv (Proxy :: _ ("MESSAGE" :: String)) env
3636
actual `shouldEqual` expected
3737

3838
it "indicates when parsing a value has failed" do
3939
let
4040
env = FO.fromHomogeneous { "DEBUG": "50" }
4141
expected = Left (EnvParseError "DEBUG")
42-
actual = fromEnv (Proxy :: _ (debug :: Boolean <: "DEBUG")) env
42+
actual = fromEnv (Proxy :: _ ("DEBUG" :: Boolean)) env
4343
actual `shouldEqual` expected
4444

4545
it "parses boolean values" do
4646
traverse_
4747
( \({ given, expected }) ->
4848
shouldEqual
49-
( fromEnv (Proxy :: _ (actual :: Boolean <: "A"))
49+
( fromEnv (Proxy :: _ ("A" :: Boolean))
5050
(FO.fromHomogeneous { "A": given })
5151
)
52-
(Right { actual: expected })
52+
(Right { "A": expected })
5353
)
5454
[ { given: "0", expected: false }
5555
, { given: "false", expected: false }
@@ -60,34 +60,34 @@ main = launchAff_ $ runSpec [ consoleReporter ] $
6060
it "parses integer values" do
6161
let
6262
env = FO.fromHomogeneous { "VALUE": "123" }
63-
expected = Right { value: 123 }
64-
actual = fromEnv (Proxy :: _ (value :: Int <: "VALUE")) env
63+
expected = Right { "VALUE": 123 }
64+
actual = fromEnv (Proxy :: _ ("VALUE" :: Int)) env
6565
actual `shouldEqual` expected
6666

6767
it "parses character values" do
6868
let
6969
env = FO.fromHomogeneous { "VALUE": "x" }
70-
expected = Right { value: 'x' }
71-
actual = fromEnv (Proxy :: _ (value :: Char <: "VALUE")) env
70+
expected = Right { "VALUE": 'x' }
71+
actual = fromEnv (Proxy :: _ ("VALUE" :: Char)) env
7272
actual `shouldEqual` expected
7373

7474
it "parses number values" do
7575
let
7676
env = FO.fromHomogeneous { "VALUE": "123.456" }
77-
expected = Right { value: 123.456 }
78-
actual = fromEnv (Proxy :: _ (value :: Number <: "VALUE")) env
77+
expected = Right { "VALUE": 123.456 }
78+
actual = fromEnv (Proxy :: _ ("VALUE" :: Number)) env
7979
actual `shouldEqual` expected
8080

8181
it "parses optional values" do
8282
let
8383
env = FO.fromHomogeneous { "VALUE": "Hello" }
84-
expected = Right { value: Just "Hello" }
85-
actual = fromEnv (Proxy :: _ (value :: Maybe String <: "VALUE")) env
84+
expected = Right { "VALUE": Just "Hello" }
85+
actual = fromEnv (Proxy :: _ ("VALUE" :: Maybe String)) env
8686
actual `shouldEqual` expected
8787

8888
it "allows optional values to be absent" do
8989
let
90-
expected = Right { value: Nothing }
91-
actual = fromEnv (Proxy :: _ (value :: Maybe String <: "VALUE"))
90+
expected = Right { "VALUE": Nothing }
91+
actual = fromEnv (Proxy :: _ ("VALUE" :: Maybe String))
9292
FO.empty
9393
actual `shouldEqual` expected

0 commit comments

Comments
 (0)