Support Text and Int in Envy
This commit is contained in:
parent
c69a1114b8
commit
01acb5b0e9
21
src/Envy.hs
21
src/Envy.hs
@ -2,6 +2,7 @@
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
|
||||
module Envy
|
||||
( type (=@@)
|
||||
@ -22,13 +23,16 @@ import Data.Char (isLower, isUpper, toUpper)
|
||||
import Data.Kind (Type)
|
||||
import Data.Proxy (Proxy (..))
|
||||
import Data.Ratio ((%))
|
||||
import Data.Text (Text)
|
||||
import Data.Typeable (Typeable, typeRep)
|
||||
import GHC.Generics (C, D, Generic, K1 (..), M1 (..), Meta (..), Rec0, Rep, S, to, (:*:) (..))
|
||||
import GHC.TypeLits (KnownNat, KnownSymbol, natVal, symbolVal)
|
||||
import GHC.TypeLits (KnownNat, KnownSymbol, natVal, symbolVal, type (<=))
|
||||
import System.Environment (getEnvironment)
|
||||
import Text.Printf (printf)
|
||||
import Text.Read (readEither)
|
||||
|
||||
import qualified Data.Text as Text
|
||||
|
||||
data ConfigVariant = Spec | Value
|
||||
|
||||
data Required t
|
||||
@ -113,15 +117,30 @@ class ProvidesDefault t d where
|
||||
instance ReadEnvVar Integer where
|
||||
readEnvVar = readEither
|
||||
|
||||
-- TODO: Support negative integers (e.g. (Negate n))
|
||||
instance (KnownNat n) => ProvidesDefault Integer n where
|
||||
getDefault Proxy = natVal (Proxy @n)
|
||||
|
||||
instance ReadEnvVar Int where
|
||||
readEnvVar = readEither
|
||||
|
||||
-- TODO: Support negative integers (e.g. (Negate n))
|
||||
-- This instance assumes that @Int@ is a 64-bit integer and enforces its range on the type level.
|
||||
instance (KnownNat n, n <= 9223372036854775807) => ProvidesDefault Int n where
|
||||
getDefault Proxy = fromInteger $ natVal (Proxy @n)
|
||||
|
||||
instance ReadEnvVar String where
|
||||
readEnvVar = Right
|
||||
|
||||
instance (KnownSymbol s) => ProvidesDefault String s where
|
||||
getDefault Proxy = symbolVal (Proxy @s)
|
||||
|
||||
instance ReadEnvVar Text where
|
||||
readEnvVar = fmap Text.pack . readEnvVar
|
||||
|
||||
instance (KnownSymbol s) => ProvidesDefault Text s where
|
||||
getDefault Proxy = Text.pack $ getDefault (Proxy @s)
|
||||
|
||||
instance ReadEnvVar Rational where
|
||||
readEnvVar = readEither
|
||||
|
||||
|
||||
Loading…
x
Reference in New Issue
Block a user