burrito-2.0.1.2: Parse and render URI templates.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Burrito

Description

Burrito is a Haskell library for parsing and rendering URI templates.

According to RFC 6570: "A URI Template is a compact sequence of characters for describing a range of Uniform Resource Identifiers through variable expansion." Burrito implements URI templates according to the specification in that RFC.

The term "uniform resource identifiers" (URI) is often used interchangeably with other related terms like "internationalized resource identifier" (IRI), "uniform resource locator" (URL), and "uniform resource name" (URN). Burrito can be used for all of these. If you want to get technical, its input must be a valid IRI and its output will be a valid URI or URN.

Although Burrito is primarily intended to be used with HTTP and HTTPS URIs, it should work with other schemes as well.

If you're not already familiar with URI templates, I recommend reading the overview of the RFC. It's short, to the point, and easy to understand.

Assuming you're familiar with URI templates, here's a simple example to show you how Burrito works:

>>> import Burrito
>>> let Just template = parse "http://example/search{?query}"
>>> expand [("query", stringValue "chorizo")] template
"http://example.com/search?query=chorizo"

In short, use parse to parse templates and expand to render them.

Synopsis

Documentation

parse :: String -> Maybe Template Source #

Attempts to parse a string as a URI template. If parsing fails, this will return Nothing. Otherwise it will return Just the parsed template.

Parsing will usually succeed, but it can fail if the input string contains characters that are not valid in IRIs (like ^) or if the input string contains an invalid template expression (like {!}). To include characters that aren't valid in IRIs, percent encode them (like %5E).

>>> parse "invalid template"
Nothing
>>> parse "valid-template"
Just (Template ...)

render :: Template -> String Source #

Renders a template back into a string. This is essentially the opposite of parse. Usually you'll want to use expand to actually substitute variables in the template, but this can be useful for printing out the template itself

>>> render <$> parse "valid-template"
Just "valid-template"
>>> render <$> parse "{var}"
Just "{var}"

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"

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

Matches a string against a template. This is essentially the opposite of expand.

Since there isn't always one unique match, this function returns all the possibilities. It's up to you to select the one that makes the most sense, or to simply grab the first one if you don't care.

>>> match "" <$> parse "no-match"
Just []
>>> match "no-variables" <$> parse "no-variables"
Just [[]]
>>> match "1-match" <$> parse "{one}-match"
Just [[("one",String "1")]]

Be warned that the number of possible matches can grow quickly if your template has variables next to each other without any separators.

>>> let Just template = parse "{a}{b}"
>>> mapM_ print $ match "ab" template
[("a",String "a"),("b",String "b")]
[("a",String "ab"),("b",String "")]
[("a",String "ab")]
[("a",String ""),("b",String "ab")]
[("b",String "ab")]

Matching supports everything except explode modifiers ({a*}), list values, and dictionary values.

uriTemplate :: QuasiQuoter Source #

This can be used together with the QuasiQuotes language extension to parse a URI template at compile time. This is convenient because it allows you to verify the validity of the template when you compile your file as opposed to when you run it.

>>> :set -XQuasiQuotes
>>> import Burrito
>>> let template = [uriTemplate|http://example/search{?query}|]
>>> let values = [("query", stringValue "chorizo")]
>>> expand values template
"http://example/search?query=chorizo"

Note that you cannot use escape sequences in this quasi-quoter. For example, this is invalid: [uriTemplate|\xa0|]. You can however use percent encoded triples as normal. So this is valid: [uriTemplate|%c2%a0|].

expandTH :: [(String, Value)] -> Template -> Q Exp Source #

This can be used together with the TemplateHaskell language extension to expand a URI template at compile time. This is slightly different from expand in that missing variables will throw an exception. This is convenient because it allows you to verify that all of the variables have been supplied at compile time.

>>> :set -XQuasiQuotes -XTemplateHaskell
>>> import Burrito
>>> $( expandTH [("foo", stringValue "bar")] [uriTemplate|l-{foo}-r|] )
"l-bar-r"

data Template Source #

Represents a URI template.

Instances

Instances details
Data Template Source # 
Instance details

Defined in Burrito.Internal.Type.Template

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Template -> c Template #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Template #

toConstr :: Template -> Constr #

dataTypeOf :: Template -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Template) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Template) #

gmapT :: (forall b. Data b => b -> b) -> Template -> Template #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Template -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Template -> r #

gmapQ :: (forall d. Data d => d -> u) -> Template -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Template -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Template -> m Template #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Template -> m Template #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Template -> m Template #

Show Template Source # 
Instance details

Defined in Burrito.Internal.Type.Template

Eq Template Source # 
Instance details

Defined in Burrito.Internal.Type.Template

Ord Template Source # 
Instance details

Defined in Burrito.Internal.Type.Template

data Value Source #

Represents a value that can be substituted into a template. Can be a string, a list, or dictionary (which is called an associative array in the RFC).

Instances

Instances details
Data Value Source # 
Instance details

Defined in Burrito.Internal.Type.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Show Value Source # 
Instance details

Defined in Burrito.Internal.Type.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source # 
Instance details

Defined in Burrito.Internal.Type.Value

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Ord Value Source # 
Instance details

Defined in Burrito.Internal.Type.Value

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

stringValue :: String -> Value Source #

Constructs a string value.

listValue :: [String] -> Value Source #

Constructs a list value.

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

Constructs a dictionary value.