Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Interpolation
Synopsis
- newtype TemplateKey = TemplateKey {}
- newtype TemplateValue = TemplateValue {}
- data Template a = Template {}
- data Uninterpolated a
- data InterpolationFailure
- newtype InterpolationContext = InterpolationContext {}
- class FromTemplateValue a where
- parseTemplateValue :: TemplateValue -> Maybe a
- class ToTemplateValue a where
- toTemplateValue :: a -> TemplateValue
- newtype Interpolator templates identities = Interpolator {
- runInterpolator :: templates -> Reader InterpolationContext (Validation [InterpolationFailure] identities)
- runTemplate :: FromTemplateValue a => Interpolator (Uninterpolated a) a
- mkInterpolationContext :: MonadIO m => m InterpolationContext
- interpolateWithContext :: (Default Interpolator templates identities, MonadIO m) => templates -> m (Either [InterpolationFailure] identities)
- interpolateWithContextExplicit :: MonadIO m => Interpolator templates identities -> templates -> m (Either [InterpolationFailure] identities)
- maybeGen :: Gen a -> Gen (Maybe a)
- noEnv :: Gen Text
- varNameAllowed :: Gen Text
Documentation
newtype TemplateKey Source #
Newtype wrapper for an environment variable key.
Constructors
TemplateKey | |
Fields |
Instances
Eq TemplateKey Source # | |
Defined in Data.Interpolation | |
Ord TemplateKey Source # | |
Defined in Data.Interpolation Methods compare :: TemplateKey -> TemplateKey -> Ordering # (<) :: TemplateKey -> TemplateKey -> Bool # (<=) :: TemplateKey -> TemplateKey -> Bool # (>) :: TemplateKey -> TemplateKey -> Bool # (>=) :: TemplateKey -> TemplateKey -> Bool # max :: TemplateKey -> TemplateKey -> TemplateKey # min :: TemplateKey -> TemplateKey -> TemplateKey # | |
Show TemplateKey Source # | |
Defined in Data.Interpolation Methods showsPrec :: Int -> TemplateKey -> ShowS # show :: TemplateKey -> String # showList :: [TemplateKey] -> ShowS # | |
Arbitrary TemplateKey Source # | |
Defined in Data.Interpolation | |
ToJSON TemplateKey Source # | |
Defined in Data.Interpolation Methods toJSON :: TemplateKey -> Value # toEncoding :: TemplateKey -> Encoding # toJSONList :: [TemplateKey] -> Value # toEncodingList :: [TemplateKey] -> Encoding # | |
FromJSON TemplateKey Source # | |
Defined in Data.Interpolation |
newtype TemplateValue Source #
Newtype wrapper for an environment variable value.
Constructors
TemplateValue | |
Fields |
Instances
Type for a value that is described by '_env:ENVIRONMENT_VARIABLE:default' in JSON.
Constructors
Template | |
Fields
|
Instances
Eq a => Eq (Template a) Source # | |
Ord a => Ord (Template a) Source # | |
Show a => Show (Template a) Source # | |
ToTemplateValue a => ToJSON (Template a) Source # | |
Defined in Data.Interpolation | |
FromTemplateValue a => FromJSON (Template a) Source # | |
data Uninterpolated a Source #
Type for a value that can be described either with '_env...' or as just a literal value in JSON.
Instances
data InterpolationFailure Source #
Constructors
InterpolationFailureKeyNotFound TemplateKey | |
InterpolationFailureValueNotReadable TemplateKey TemplateValue |
Instances
Eq InterpolationFailure Source # | |
Defined in Data.Interpolation Methods (==) :: InterpolationFailure -> InterpolationFailure -> Bool # (/=) :: InterpolationFailure -> InterpolationFailure -> Bool # | |
Ord InterpolationFailure Source # | |
Defined in Data.Interpolation Methods compare :: InterpolationFailure -> InterpolationFailure -> Ordering # (<) :: InterpolationFailure -> InterpolationFailure -> Bool # (<=) :: InterpolationFailure -> InterpolationFailure -> Bool # (>) :: InterpolationFailure -> InterpolationFailure -> Bool # (>=) :: InterpolationFailure -> InterpolationFailure -> Bool # max :: InterpolationFailure -> InterpolationFailure -> InterpolationFailure # min :: InterpolationFailure -> InterpolationFailure -> InterpolationFailure # | |
Show InterpolationFailure Source # | |
Defined in Data.Interpolation Methods showsPrec :: Int -> InterpolationFailure -> ShowS # show :: InterpolationFailure -> String # showList :: [InterpolationFailure] -> ShowS # |
newtype InterpolationContext Source #
Constructors
InterpolationContext | |
class FromTemplateValue a where Source #
A class for parsing environment variable values, which should only be defined on primitives.
Similar to Read
except that for text-type values it should parse using identity.
Methods
parseTemplateValue :: TemplateValue -> Maybe a Source #
Instances
FromTemplateValue Bool Source # | |
Defined in Data.Interpolation Methods | |
FromTemplateValue Int Source # | |
Defined in Data.Interpolation Methods | |
FromTemplateValue String Source # | |
Defined in Data.Interpolation Methods parseTemplateValue :: TemplateValue -> Maybe String Source # | |
FromTemplateValue Text Source # | |
Defined in Data.Interpolation Methods |
class ToTemplateValue a where Source #
A class for showing environment variable values, which should only be defined on primitives.
Similar to Show
except that for text-type values it should use identity.
Methods
toTemplateValue :: a -> TemplateValue Source #
Instances
ToTemplateValue Bool Source # | |
Defined in Data.Interpolation Methods toTemplateValue :: Bool -> TemplateValue Source # | |
ToTemplateValue Int Source # | |
Defined in Data.Interpolation Methods toTemplateValue :: Int -> TemplateValue Source # | |
ToTemplateValue String Source # | |
Defined in Data.Interpolation Methods | |
ToTemplateValue Text Source # | |
Defined in Data.Interpolation Methods toTemplateValue :: Text -> TemplateValue Source # |
newtype Interpolator templates identities Source #
Constructors
Interpolator | |
Fields
|
Instances
runTemplate :: FromTemplateValue a => Interpolator (Uninterpolated a) a Source #
Run a template using the interpolation context and failing if the value is not found or not readable.
mkInterpolationContext :: MonadIO m => m InterpolationContext Source #
interpolateWithContext :: (Default Interpolator templates identities, MonadIO m) => templates -> m (Either [InterpolationFailure] identities) Source #
interpolateWithContextExplicit :: MonadIO m => Interpolator templates identities -> templates -> m (Either [InterpolationFailure] identities) Source #
varNameAllowed :: Gen Text Source #