uri-templater-0.3.1.0: Parsing & Quasiquoting for RFC 6570 URI Templates

Safe HaskellNone
LanguageHaskell98

Network.URI.Template

Contents

Description

RFC 6570 URI templates are a convenient mechanism for constructing URIs in a standardized way. They provide the ability to escape the interpolated values appropriately, format them for the appropriate part of the URI, and can handle list-like ([], Vector) and associative inputs (such as associative lists, Maps, HashMaps).

This implementation supports outputting these URI fragments to all widely-used textual/bytestring formats, and provides basic facilities for extending the URI rendering to support other output formats.

Synopsis

Documentation

Due to the large number of different interpolation options available, it is arguably easiest to view an example of each sort of interpolation to see how it works. RFC 6570 itself https://tools.ietf.org/html/rfc6570 also provides a large number of these same examples, so it may help to look at it directly.

For these examples, the following values are assumed:

var :: TemplateString
var = "value"

semi :: TemplateString
semi = ";"

hello :: TemplateString
hello = "Hello World!"

path :: TemplateString
path = "/foo/bar"

list :: [TemplateString]
list = ["red", "green", "blue"]

keys :: AList TemplateString TemplateString
keys = AList [("semi", ";"), ("dot", "."), ("comma", ",")]

Simple interpolation

Simple string expansion is the default expression type when no operator is given.

For each defined variable in the variable-list, perform variable expansion. If more than one variable has a defined value, append a comma (",") to the result string as a separator between variable expansions.

Without modifiers

>>> [uri|{var}|]
value

Interpolating with a length modifier

>>> [uri|{var:3}|]
val

Interpolating multiple values:

>>> [uri|{var,hello}|]
value,hello

Interpolating a list:

>>> [uri|{list}|]
red,green,blue

Exploding a list (not super useful without modifiers):

>>> [uri|{list*}|]
red,green,blue

Interpolating associative values:

>>> [uri|{keys}|]
semi,%3B,dot,.,comma,%2C

Exploding associative values

>>> [uri|{keys*}|]
semi=%3B,dot=.,comma=%2C

Unescaped interpolation

>>> [uri|{+path:6}/here|]
/foo/b/here
>>> [uri|{+list}|]
red,green,blue
>>> [uri|{+list*}|]
red,green,blue
>>> [uri|{+keys}]
semi,;,dot,.,comma,,
>>> [uri|{+keys*}]
semi=;,dot=.,comma=,

Path piece interpolation

Path segment expansion, as indicated by the slash ("/"), is useful for describing URI path hierarchies.

For each defined variable in the variable-list, append "/" to the result string and then perform variable expansion.

Note that the expansion process for path segment expansion is identical to that of label expansion aside from the substitution of "" instead of ".". However, unlike ".", a "" is a reserved character and will be percent-encoded if found in a value.

>>> [uri|{/var:1,var}|]
/v/value
>>> [uri|{/list}|]
/red,green,blue
>>> [uri|{/list*}]
/red/green/blue

Query param interpolation

>>> [uri|{?var:3}|]
?var=val
>>> [uri|{?list}|]
?list=red,green.blue
>>> [uri|{?list*}|]
?list=red&list=green&list=blue
>>> [uri|{?keys}|]
?keys=semi,%3B,dot,.,comma,%2C
>>> [uri|{?keys*}|]
?semi=%3B&dot=.&comma=%2C

Continued query param interpolation

>>> [uri|{?var:3}|]
&var=val
>>> [uri|{?list}|]
&list=red,green.blue
>>> [uri|{?list*}|]
&list=red&list=green&list=blue
>>> [uri|{?keys}|]
&keys=semi,%3B,dot,.,comma,%2C
>>> [uri|{?keys*}|]
&semi=%3B&dot=.&comma=%2C

Label interpolation

Label expansion, as indicated by the dot (".") operator is useful for describing URI spaces with varying domain names or path selectors (e.g., filename extensions).

>>> [uri|X{.var:3}|]
X.val
>>> [uri|X{.list}|]
X.red,green,blue
>>> [uri|X{.list*}|]
X.red.green.blue
>>> [uri|X{.keys}|]
X.semi,%3B,dot,.,comma,%2C
>>> [uri|X{.keys*}|]
X.semi=%3B.dot=..comma=%2C

Fragment interpolation

Path-style parameter expansion, as indicated by the semicolon (";") is useful for describing URI path parameters, such as "path;property" or "path;name=value".

>>> [uri|{;hello:5}|]
;hello=Hello
>>> [uri|{;list}|]
;list=red,green,blue
>>> [uri|{;list*}|]
;list=red;list=green;list=blue
>>> [uri|{;keys}|]
;keys=semi,%3B,dot,.,comma,%2C
>>> [uri|{;keys*}|]
;semi=%3B;dot=.;comma=%2C

Security Considerations

A URI Template does not contain active or executable content. However, it might be possible to craft unanticipated URIs if an attacker is given control over the template or over the variable values within an expression that allows reserved characters in the expansion. In either case, the security considerations are largely determined by who provides the template, who provides the values to use for variables within the template, in what execution context the expansion occurs (client or server), and where the resulting URIs are used.

Quasi-Quoting URI templates

uri :: QuasiQuoter Source #

URI quasiquoter. Can only be used in expressions, not for top-level declarations

Manually parsing, constructing, & writing URI templates

class ToTemplateValue a where Source #

Minimal complete definition

toTemplateValue

Associated Types

type TemplateRep a :: * Source #

Instances

ToTemplateValue Bool Source # 
ToTemplateValue Double Source # 
ToTemplateValue Float Source # 
ToTemplateValue Int Source # 

Associated Types

type TemplateRep Int :: * Source #

ToTemplateValue Int8 Source # 
ToTemplateValue Int16 Source # 
ToTemplateValue Int32 Source # 
ToTemplateValue Int64 Source # 
ToTemplateValue Integer Source # 
ToTemplateValue Ordering Source # 
ToTemplateValue Word Source # 
ToTemplateValue Word8 Source # 
ToTemplateValue Word16 Source # 
ToTemplateValue Word32 Source # 
ToTemplateValue Word64 Source # 
ToTemplateValue () Source # 

Associated Types

type TemplateRep () :: * Source #

ToTemplateValue Text Source # 
ToTemplateValue Text Source # 
ToTemplateValue Natural Source # 
ToTemplateValue Version Source # 
ToTemplateValue All Source # 

Associated Types

type TemplateRep All :: * Source #

ToTemplateValue Any Source # 

Associated Types

type TemplateRep Any :: * Source #

ToTemplateValue LocalTime Source # 
ToTemplateValue ZonedTime Source # 
ToTemplateValue TimeOfDay Source # 
ToTemplateValue UTCTime Source # 
ToTemplateValue NominalDiffTime Source # 
ToTemplateValue Day Source # 

Associated Types

type TemplateRep Day :: * Source #

ToTemplateValue UUID Source # 
ToTemplateValue TemplateString Source # 
(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue [a] Source # 

Associated Types

type TemplateRep [a] :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (Maybe a) Source # 

Associated Types

type TemplateRep (Maybe a) :: * Source #

ToTemplateValue a => ToTemplateValue (Identity a) Source # 

Associated Types

type TemplateRep (Identity a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (NonEmpty a) Source # 

Associated Types

type TemplateRep (NonEmpty a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (Dual a) Source # 

Associated Types

type TemplateRep (Dual a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (Sum a) Source # 

Associated Types

type TemplateRep (Sum a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (Product a) Source # 

Associated Types

type TemplateRep (Product a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (First a) Source # 

Associated Types

type TemplateRep (First a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (Last a) Source # 

Associated Types

type TemplateRep (Last a) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single) => ToTemplateValue (Vector a) Source # 

Associated Types

type TemplateRep (Vector a) :: * Source #

(ToTemplateValue a, ToTemplateValue b, (~) * (TemplateRep a) Single, (~) * (TemplateRep b) Single) => ToTemplateValue (Either a b) Source # 

Associated Types

type TemplateRep (Either a b) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single, ToTemplateValue b, (~) * (TemplateRep b) Single) => ToTemplateValue (a, b) Source # 

Associated Types

type TemplateRep (a, b) :: * Source #

Methods

toTemplateValue :: (a, b) -> TemplateValue (TemplateRep (a, b)) Source #

(ToTemplateValue k, (~) * (TemplateRep k) Single, ToTemplateValue v, (~) * (TemplateRep v) Single) => ToTemplateValue (Map k v) Source # 

Associated Types

type TemplateRep (Map k v) :: * Source #

(ToTemplateValue k, (~) * (TemplateRep k) Single, ToTemplateValue v, (~) * (TemplateRep v) Single) => ToTemplateValue (HashMap k v) Source # 

Associated Types

type TemplateRep (HashMap k v) :: * Source #

(ToTemplateValue k, (~) * (TemplateRep k) Single, ToTemplateValue v, (~) * (TemplateRep v) Single) => ToTemplateValue (AList k v) Source # 

Associated Types

type TemplateRep (AList k v) :: * Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single, ToTemplateValue b, (~) * (TemplateRep b) Single, ToTemplateValue c, (~) * (TemplateRep c) Single) => ToTemplateValue (a, b, c) Source # 

Associated Types

type TemplateRep (a, b, c) :: * Source #

Methods

toTemplateValue :: (a, b, c) -> TemplateValue (TemplateRep (a, b, c)) Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single, ToTemplateValue b, (~) * (TemplateRep b) Single, ToTemplateValue c, (~) * (TemplateRep c) Single, ToTemplateValue d, (~) * (TemplateRep d) Single) => ToTemplateValue (a, b, c, d) Source # 

Associated Types

type TemplateRep (a, b, c, d) :: * Source #

Methods

toTemplateValue :: (a, b, c, d) -> TemplateValue (TemplateRep (a, b, c, d)) Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single, ToTemplateValue b, (~) * (TemplateRep b) Single, ToTemplateValue c, (~) * (TemplateRep c) Single, ToTemplateValue d, (~) * (TemplateRep d) Single, ToTemplateValue e, (~) * (TemplateRep e) Single) => ToTemplateValue (a, b, c, d, e) Source # 

Associated Types

type TemplateRep (a, b, c, d, e) :: * Source #

Methods

toTemplateValue :: (a, b, c, d, e) -> TemplateValue (TemplateRep (a, b, c, d, e)) Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single, ToTemplateValue b, (~) * (TemplateRep b) Single, ToTemplateValue c, (~) * (TemplateRep c) Single, ToTemplateValue d, (~) * (TemplateRep d) Single, ToTemplateValue e, (~) * (TemplateRep e) Single, ToTemplateValue f, (~) * (TemplateRep f) Single) => ToTemplateValue (a, b, c, d, e, f) Source # 

Associated Types

type TemplateRep (a, b, c, d, e, f) :: * Source #

Methods

toTemplateValue :: (a, b, c, d, e, f) -> TemplateValue (TemplateRep (a, b, c, d, e, f)) Source #

(ToTemplateValue a, (~) * (TemplateRep a) Single, ToTemplateValue b, (~) * (TemplateRep b) Single, ToTemplateValue c, (~) * (TemplateRep c) Single, ToTemplateValue d, (~) * (TemplateRep d) Single, ToTemplateValue e, (~) * (TemplateRep e) Single, ToTemplateValue f, (~) * (TemplateRep f) Single, ToTemplateValue g, (~) * (TemplateRep g) Single) => ToTemplateValue (a, b, c, d, e, f, g) Source # 

Associated Types

type TemplateRep (a, b, c, d, e, f, g) :: * Source #

Methods

toTemplateValue :: (a, b, c, d, e, f, g) -> TemplateValue (TemplateRep (a, b, c, d, e, f, g)) Source #

newtype AList k v Source #

A simple list of key value pairs. Useful when you want to be able to have multiple duplicate keys, which Map and HashMap don't support.

Constructors

AList 

Fields

Instances

(Eq v, Eq k) => Eq (AList k v) Source # 

Methods

(==) :: AList k v -> AList k v -> Bool #

(/=) :: AList k v -> AList k v -> Bool #

(Read v, Read k) => Read (AList k v) Source # 
(Show v, Show k) => Show (AList k v) Source # 

Methods

showsPrec :: Int -> AList k v -> ShowS #

show :: AList k v -> String #

showList :: [AList k v] -> ShowS #

(ToTemplateValue k, (~) * (TemplateRep k) Single, ToTemplateValue v, (~) * (TemplateRep v) Single) => ToTemplateValue (AList k v) Source # 

Associated Types

type TemplateRep (AList k v) :: * Source #

type TemplateRep (AList k v) Source # 

type UriTemplate = [TemplateSegment] Source #

A URI template is fundamentally a bunch of segments that are either constants or else an interpolation

data TemplateSegment Source #

Constructors

Literal String

A literal string. No URI escaping will be performed

Embed Modifier [Variable]

An interpolation can have multiple variables (separated by commas in the textual format)

data Modifier Source #

How an interpolated value should be rendered

Constructors

Simple

No prefix

Reserved

Prefixed by +

Fragment

Prefixed by #

Label

Prefixed by .

PathSegment

Prefixed by /

PathParameter

Prefixed by ;

Query

Prefixed by ?

QueryContinuation

Prefixed by &

data TemplateValue a where Source #

All values must reduce to a single value pair, an associative list of keys and values, or a list of values without keys.

Implementing a new output format for URI templates

class Monoid (Builder a) => Buildable a where Source #

Minimal complete definition

build, addChar, addString

Associated Types

type Builder a Source #

Methods

build :: Builder a -> a Source #

Convert the intermediate output into the end result

addChar :: Proxy a -> Char -> Builder a Source #

Construct an appendable character representation

addString :: Proxy a -> String -> Builder a Source #

Construct an appendable string representation

Instances

Buildable ByteString Source # 
Buildable ByteString Source # 
Buildable Text Source # 
Buildable Text Source # 
Buildable String Source # 
Buildable Builder Source # 
Buildable Builder Source #