Support Text and Int in Envy

This commit is contained in:
Paul Brinkmeier 2025-09-17 18:56:13 +02:00
parent c69a1114b8
commit 01acb5b0e9

View File

@ -2,6 +2,7 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Envy module Envy
( type (=@@) ( type (=@@)
@ -22,13 +23,16 @@ import Data.Char (isLower, isUpper, toUpper)
import Data.Kind (Type) import Data.Kind (Type)
import Data.Proxy (Proxy (..)) import Data.Proxy (Proxy (..))
import Data.Ratio ((%)) import Data.Ratio ((%))
import Data.Text (Text)
import Data.Typeable (Typeable, typeRep) import Data.Typeable (Typeable, typeRep)
import GHC.Generics (C, D, Generic, K1 (..), M1 (..), Meta (..), Rec0, Rep, S, to, (:*:) (..)) 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 System.Environment (getEnvironment)
import Text.Printf (printf) import Text.Printf (printf)
import Text.Read (readEither) import Text.Read (readEither)
import qualified Data.Text as Text
data ConfigVariant = Spec | Value data ConfigVariant = Spec | Value
data Required t data Required t
@ -113,15 +117,30 @@ class ProvidesDefault t d where
instance ReadEnvVar Integer where instance ReadEnvVar Integer where
readEnvVar = readEither readEnvVar = readEither
-- TODO: Support negative integers (e.g. (Negate n))
instance (KnownNat n) => ProvidesDefault Integer n where instance (KnownNat n) => ProvidesDefault Integer n where
getDefault Proxy = natVal (Proxy @n) 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 instance ReadEnvVar String where
readEnvVar = Right readEnvVar = Right
instance (KnownSymbol s) => ProvidesDefault String s where instance (KnownSymbol s) => ProvidesDefault String s where
getDefault Proxy = symbolVal (Proxy @s) 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 instance ReadEnvVar Rational where
readEnvVar = readEither readEnvVar = readEither