burrito-1.1.0.2: Parse and render URI templates.

Safe HaskellSafe
LanguageHaskell2010

Burrito.Internal.Expand

Synopsis

Documentation

expand :: [(String, Value)] -> Template -> String Source #

Expands a template using the given values. Unlike parsing, expansion always succeeds. If no value is given for a variable, it will simply not appear in the output.

>>> expand [] <$> parse "valid-template"
Just "valid-template"
>>> expand [] <$> parse "template:{example}"
Just "template:"
>>> expand [("example", stringValue "true")] <$> parse "template:{example}"
Just "template:true"

expandWith :: Monad m => (Text -> m (Maybe Value)) -> Template -> m Builder Source #

This is like expand except that it gives you more control over how variables are expanded. If you can, use expand. It's simpler.

Instead of passing in a static mapping form names to values, you pass in a function that is used to look up values on the fly. This can be useful if computing values takes a while or requires some impure actions.

>>> expandWith (\ x -> [Nothing, Just . stringValue $ unpack x]) <$> parse "template:{example}"
Just ["template:","template:example"]
>>> let Just template = parse "user={USER}"
>>> expandWith (fmap (fmap stringValue) . lookupEnv . unpack) template
"user=taylor"

Note that as the RFC specifies, the given function will be called at most once for each variable in the template.

>>> let Just template = parse "{a}{a}"
>>> expandWith (\ x -> do { putStrLn $ "-- expanding " <> show x; pure . Just $ Burrito.stringValue "A" }) template
-- expanding "a"
"AA"

cached :: Monad m => (Text -> m (Maybe Value)) -> Name -> CacheT m (Maybe Value) Source #

items :: (Operator -> Variable -> a -> [Builder]) -> Operator -> Variable -> [a] -> Maybe Builder Source #