Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- expand :: [(String, Value)] -> Template -> String
- expandWith :: Monad m => (Text -> m (Maybe Value)) -> Template -> m Builder
- type CacheT = StateT (Map Text (Maybe Value))
- cached :: Monad m => (Text -> m (Maybe Value)) -> Name -> CacheT m (Maybe Value)
- template :: Monad m => (Name -> CacheT m (Maybe Value)) -> Template -> CacheT m Builder
- token :: Monad m => (Name -> CacheT m (Maybe Value)) -> Token -> CacheT m Builder
- expression :: Monad m => (Name -> CacheT m (Maybe Value)) -> Expression -> CacheT m Builder
- separator :: Operator -> Builder
- prefix :: Operator -> Builder
- variable :: Monad m => (Name -> CacheT m (Maybe Value)) -> Operator -> Variable -> CacheT m (Maybe Builder)
- value :: Operator -> Variable -> Value -> Maybe Builder
- dictionaryValue :: Operator -> Variable -> [(Text, Text)] -> Maybe Builder
- listValue :: Operator -> Variable -> [Text] -> Maybe Builder
- items :: (Operator -> Variable -> a -> [Builder]) -> Operator -> Variable -> [a] -> Maybe Builder
- label :: Bool -> Variable -> Builder
- name :: Name -> Builder
- field :: Field -> Builder
- character :: (Char -> Bool) -> Character tag -> Builder
- stringValue :: Operator -> Variable -> Text -> Builder
- string :: Operator -> Modifier -> Text -> Builder
- isAllowed :: Char -> Bool
- isUnreserved :: Char -> Bool
- isReserved :: Char -> Bool
- unencodedCharacter :: (Char -> Bool) -> Char -> Builder
- encodeCharacter :: Char -> [(Digit, Digit)]
- literal :: Literal -> Builder
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 from 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"
expression :: Monad m => (Name -> CacheT m (Maybe Value)) -> Expression -> CacheT m Builder Source #
variable :: Monad m => (Name -> CacheT m (Maybe Value)) -> Operator -> Variable -> CacheT m (Maybe Builder) Source #
items :: (Operator -> Variable -> a -> [Builder]) -> Operator -> Variable -> [a] -> Maybe Builder Source #
isUnreserved :: Char -> Bool Source #
isReserved :: Char -> Bool Source #