network-uri-template: TODO

[ agpl, library, program, unclassified ] [ Propose Tags ] [ Report a vulnerability ]

Please see README.md


[Skip to Readme]

Modules

  • Network
    • URI
      • Network.URI.Template
        • Network.URI.Template.Expand
        • Network.URI.Template.Internal
          • Network.URI.Template.Internal.Expression
          • Network.URI.Template.Internal.Modifier
          • Network.URI.Template.Internal.Operator
          • Network.URI.Template.Internal.Parse
          • Network.URI.Template.Internal.Pretty
          • Network.URI.Template.Internal.TemplatePart
          • Network.URI.Template.Internal.VarSpec
        • Network.URI.Template.Parse
        • Network.URI.Template.VarName
        • Network.URI.Template.VarValue

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.1.0
Change log CHANGELOG.md
Dependencies base (>=4.20.2.0 && <5), containers (>=0.7), megaparsec (>=9.7.0), network-uri (>=2.6.4.2), network-uri-template, optparse-applicative (>=0.18.1.0), prettyprinter (>=1.7.1), prettyprinter-ansi-terminal (>=1.1.3), text (>=2.1.3) [details]
License AGPL-3.0-only
Author
Maintainer Pat Brisbin
Uploaded by PatrickBrisbin at 2025-11-07T19:00:42Z
Distributions
Executables network-uri-template
Downloads 4 total (4 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2025-11-07 [all 2 reports]

Readme for network-uri-template-0.1.0.0

[back to package description]

network-uri-template

Library for parsing and expanding URI Templates, as per RFC 6570.

URI Templates

An example from the RFC:

For example, the following URI Template includes a form-style parameter expression, as indicated by the "?" operator appearing before the variable names.

  http://www.example.com/foo{?query,number}

The expansion process for expressions beginning with the question- mark ("?") operator follows the same pattern as form-style interfaces on the World Wide Web:

  http://www.example.com/foo{?query,number}
                            \_____________/
                               |
                               |
          For each defined variable in [ 'query', 'number' ],
          substitute "?" if it is the first substitution or "&"
          thereafter, followed by the variable name, '=', and the
          variable's value.

If the variables have the values

  query  := "mycelium"
  number := 100

then the expansion of the above URI Template is

  http://www.example.com/foo?query=mycelium&number=100

Alternatively, if 'query' is undefined, then the expansion would be

  http://www.example.com/foo?number=100

or if both variables are undefined, then it would be

  http://www.example.com/foo

For a complete description of URI Templates, consult the RFC or see our extracted test cases.

Example

{-# LANGUAGE OverloadedStrings #-}

module Main
  ( main
  ) where

import Prelude

import Data.Text (Text)
import Data.Text.IO qualified as T
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Network.URI.Template
import System.Exit (die)

main :: IO ()
main = do
  let
    vars :: Map VarName VarValue
    vars =
      Map.fromList
        [ ("query", "mycelium")
        , ("number", "100")
        ]

    template :: Text
    template = "http://www.example.com/foo{?query,number}"

    handle = either (die . templateErrorPretty) T.putStrLn

  handle $ processTemplate vars template
  -- => http://www.example.com/foo?query=mycelium&number=100

  handle $ processTemplate (Map.delete "query" vars) template
  -- => http://www.example.com/foo?number=100

  handle $ processTemplate (Map.empty) template
  -- => http://www.example.com/foo

CLI

This project includes a small CLI to experiment with template expansion.

network-uri-template \
  --var 'query  := "mycelium"' \
  --var 'number := "100"' \
  --var 'path   := ("foo", "bar")' \
  --var 'keys   := [("sort","asc"), ("page","2")]' \
  'http://www.example.com{/path*}/foo{?query:2,number}{&keys*}'

License

This project is licensed AGPLv3. See COPYING.