interpolator-0.1.2: Runtime interpolation of environment variables in records using profunctors

Safe HaskellNone
LanguageHaskell2010

Data.Interpolation

Synopsis

Documentation

data Template a Source #

Type for a value that is described by '_env:ENVIRONMENT_VARIABLE:default' in JSON.

Instances
Eq a => Eq (Template a) Source # 
Instance details

Defined in Data.Interpolation

Methods

(==) :: Template a -> Template a -> Bool #

(/=) :: Template a -> Template a -> Bool #

Ord a => Ord (Template a) Source # 
Instance details

Defined in Data.Interpolation

Methods

compare :: Template a -> Template a -> Ordering #

(<) :: Template a -> Template a -> Bool #

(<=) :: Template a -> Template a -> Bool #

(>) :: Template a -> Template a -> Bool #

(>=) :: Template a -> Template a -> Bool #

max :: Template a -> Template a -> Template a #

min :: Template a -> Template a -> Template a #

Show a => Show (Template a) Source # 
Instance details

Defined in Data.Interpolation

Methods

showsPrec :: Int -> Template a -> ShowS #

show :: Template a -> String #

showList :: [Template a] -> ShowS #

ToTemplateValue a => ToJSON (Template a) Source # 
Instance details

Defined in Data.Interpolation

FromTemplateValue a => FromJSON (Template a) Source # 
Instance details

Defined in Data.Interpolation

data Uninterpolated a Source #

Type for a value that can be described either with '_env...' or as just a literal value in JSON.

Constructors

Templated (Template a) 
Literal a 
Instances
FromTemplateValue a => Default Interpolator (Uninterpolated a) a Source #

When we can parse template values, we can interpolate from the template.

Instance details

Defined in Data.Interpolation

Eq a => Eq (Uninterpolated a) Source # 
Instance details

Defined in Data.Interpolation

Ord a => Ord (Uninterpolated a) Source # 
Instance details

Defined in Data.Interpolation

Show a => Show (Uninterpolated a) Source # 
Instance details

Defined in Data.Interpolation

Arbitrary a => Arbitrary (Uninterpolated a) Source # 
Instance details

Defined in Data.Interpolation

Arbitrary (Uninterpolated Text) Source # 
Instance details

Defined in Data.Interpolation

(ToTemplateValue a, ToJSON a) => ToJSON (Uninterpolated a) Source # 
Instance details

Defined in Data.Interpolation

(FromTemplateValue a, FromJSON a) => FromJSON (Uninterpolated a) Source # 
Instance details

Defined in Data.Interpolation

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.

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.

newtype Interpolator templates identities Source #

Constructors

Interpolator 
Instances
Profunctor Interpolator Source # 
Instance details

Defined in Data.Interpolation

Methods

dimap :: (a -> b) -> (c -> d) -> Interpolator b c -> Interpolator a d #

lmap :: (a -> b) -> Interpolator b c -> Interpolator a c #

rmap :: (b -> c) -> Interpolator a b -> Interpolator a c #

(#.) :: Coercible c b => q b c -> Interpolator a b -> Interpolator a c #

(.#) :: Coercible b a => Interpolator b c -> q a b -> Interpolator a c #

ProductProfunctor Interpolator Source # 
Instance details

Defined in Data.Interpolation

Methods

purePP :: b -> Interpolator a b #

(****) :: Interpolator a (b -> c) -> Interpolator a b -> Interpolator a c #

empty :: Interpolator () () #

(***!) :: Interpolator a b -> Interpolator a' b' -> Interpolator (a, a') (b, b') #

SumProfunctor Interpolator Source # 
Instance details

Defined in Data.Interpolation

Methods

(+++!) :: Interpolator a b -> Interpolator a' b' -> Interpolator (Either a a') (Either b b') #

Default Interpolator a a Source #

Pure transformation for the identity interpolation. FIXME this is too clunky for overlapping instances, define an auxiliary class (or type) for IdentityInterpolation.

Instance details

Defined in Data.Interpolation

Methods

def :: Interpolator a a #

FromTemplateValue a => Default Interpolator (Uninterpolated a) a Source #

When we can parse template values, we can interpolate from the template.

Instance details

Defined in Data.Interpolation

Default Interpolator a b => Default Interpolator [a] [b] Source # 
Instance details

Defined in Data.Interpolation

Methods

def :: Interpolator [a] [b] #

Default Interpolator a b => Default Interpolator (Maybe a) (Maybe b) Source # 
Instance details

Defined in Data.Interpolation

Methods

def :: Interpolator (Maybe a) (Maybe b) #

(Default Interpolator a b, Ord a, Ord b) => Default Interpolator (Set a) (Set b) Source # 
Instance details

Defined in Data.Interpolation

Methods

def :: Interpolator (Set a) (Set b) #

Default Interpolator a b => Default Interpolator (Map k a) (Map k b) Source # 
Instance details

Defined in Data.Interpolation

Methods

def :: Interpolator (Map k a) (Map k b) #

Functor (Interpolator templates) Source # 
Instance details

Defined in Data.Interpolation

Methods

fmap :: (a -> b) -> Interpolator templates a -> Interpolator templates b #

(<$) :: a -> Interpolator templates b -> Interpolator templates a #

Applicative (Interpolator templates) Source # 
Instance details

Defined in Data.Interpolation

Methods

pure :: a -> Interpolator templates a #

(<*>) :: Interpolator templates (a -> b) -> Interpolator templates a -> Interpolator templates b #

liftA2 :: (a -> b -> c) -> Interpolator templates a -> Interpolator templates b -> Interpolator templates c #

(*>) :: Interpolator templates a -> Interpolator templates b -> Interpolator templates b #

(<*) :: Interpolator templates a -> Interpolator templates b -> Interpolator templates a #

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.

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 #