Copyright | (c) Alexey Radkov 2020-2024 |
---|---|
License | BSD-style |
Maintainer | alexey.radkov@gmail.com |
Stability | stable |
Portability | non-portable (requires Template Haskell) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
NgxExport.Tools.EDE
Description
EDE templates for parsing JSON objects from the more extra tools collection for nginx-haskell-module.
Synopsis
- extraEDEFilters :: HashMap Id Term
- renderEDETemplate :: ByteString -> ByteString -> IO ByteString
- renderEDETemplateWith :: (ByteString -> Maybe Value) -> HashMap Id Term -> ByteString -> ByteString -> IO ByteString
- renderEDETemplateFromFreeValue :: ByteString -> IO ByteString
Rendering JSON objects using EDE templates
This module allows for complex parsing of JSON objects with EDE templating language. In terms of module NgxExport.Tools.SimpleService, it exports a single-shot service compileEDETemplates to configure a list of templates parameterized by a simple key, and two variable handlers renderEDETemplate and renderEDETemplateFromFreeValue for parsing JSON objects and substitution of extracted data into provided EDE templates. The former handler is asynchronous and suitable for parsing JSON objects POSTed in a request body, while the latter is synchronous and can parse JSON objects contained in Nginx variables.
Below is a simple example.
File test_tools_extra_ede.hs
{-# LANGUAGE TemplateHaskell #-}
module TestToolsExtraEDE where
import NgxExport
import NgxExport.Tools.EDE ()
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L
import qualified Network.HTTP.Types.URI as URI
urlDecode :: ByteString -> L.ByteString
urlDecode = L.fromStrict . URI.urlDecode False
ngxExportYY
'urlDecode
We are going to use urlDecode to decode JSON values contained in HTTP cookies. Notice that we are not using any Haskell declarations from module NgxExport.Tools.EDE while still need to import this to access the three handlers from the Nginx configuration. This situation is quite valid though not usual to ghc, and to make it keep silence, an explicit empty import list was added at the end of the import stanza.
File nginx.conf
user nobody; worker_processes 2; events { worker_connections 1024; } http { default_type application/octet-stream; sendfile on; haskell load /var/lib/nginx/test_tools_extra_ede.so; haskell_run_service simpleService_compileEDETemplates $hs_EDETemplates '("/var/lib/nginx/EDE", [("user", "{{user.id}}/{{user.ops|b64}}/{{resources.path|uenc}}")])'; server { listen 8010; server_name main; error_log /tmp/nginx-test-haskell-error.log; access_log /tmp/nginx-test-haskell-access.log; location / { haskell_run_async_on_request_body renderEDETemplate $hs_user user; rewrite ^ /internal/user/$hs_user last; } location ~ ^/internal/user/(EDE\ ERROR:.*) { internal; echo_status 404; echo "Bad input: $1"; } location ~ ^/internal/user/([^/]+)/([^/]+)/([^/]+)$ { internal; echo "User id: $1, options: $2, path: $3"; } location ~ ^/internal/user/(.*) { internal; echo_status 404; echo "Unexpected input: $1"; } location /cookie { haskell_run urlDecode $hs_cookie_user $cookie_user; haskell_run renderEDETemplateFromFreeValue $hs_user_from_cookie user|$hs_cookie_user; rewrite ^ /internal/user/$hs_user_from_cookie last; } } }
There is an EDE template declared by the argument of service simpleService_compileEDETemplates. The template will be accessed later in the asynchronous body handler renderEDETemplate with key user. Path /var/lib/nginx/EDE can be used in the templates to include more rules from files located inside it, but we do not actually use this here.
The rule inside template user says: with given JSON object,
- print object id inside a top object user,
- print slash,
- print object ops inside the top object user filtered by function b64,
- print slash,
- print object path inside a top object resources filtered by function uenc.
Functions b64 and uenc are polymorphic filters in terms of EDE language. There are many filters shipped with EDE, but b64 and uenc were defined in this module.
- b64 encodes an Aeson's
Value
using base64url encoding, - uenc encodes an Aeson's
Value
using URL encoding rules.
So, basically, we used renderEDETemplate to decompose POSTed JSON objects and then rewrite requests to other locations where the URL path after substitution of the extracted and then encoded into variable $hs_user fields points to. Handler renderEDETemplateFromFreeValue in location /cookie does the same but reads JSON objects from HTTP cookie user.
A simple test
$ curl -d '{"user": {"id" : "user1", "ops": ["op1", "op2"]}, "resources": {"path": "/opt/users"}}' 'http://localhost:8010/' User id: user1, options: WyJvcDEiLCJvcDIiXQ==, path: %2Fopt%2Fusers
Let's try to send a broken (in any meaning) input value.
$ curl -d '{"user": {"id" : "user1", "ops": ["op1", "op2"]}, "resources": {"p": "/opt/users"}}' 'http://localhost:8010/' Bad input: EDE ERROR: Text.EDE.parse:1:32 error: variable resources.path doesn't exist.
Now we got response with HTTP status 404 and a comprehensive description of what went wrong. To not mess rewrite logic and error responses, variable $hs_user can be listed inside directive haskell_var_empty_on_error in the Nginx configuration.
haskell_var_empty_on_error $hs_user;
Now the variable will always be empty on errors, while the errors will still be logged by Nginx in the error log.
Let's read user data encoded in HTTP cookie user.
$ curl -b 'user=%7B%22user%22%3A%20%7B%22id%22%20%3A%20%22user1%22%2C%20%22ops%22%3A%20%5B%22op1%22%2C%20%22op2%22%5D%7D%2C%20%22resources%22%3A%20%7B%22path%22%3A%20%22%2Fopt%2Fusers%22%7D%7D' 'http://localhost:8010/cookie' User id: user1, options: WyJvcDEiLCJvcDIiXQ==, path: %2Fopt%2Fusers
extraEDEFilters :: HashMap Id Term Source #
A small collection of custom EDE filters.
The collection is used in renderEDETemplate
and contains the following
polymorphic filters:
Arguments
:: ByteString | JSON object |
-> ByteString | Key to find the EDE template |
-> IO ByteString |
Renders an EDE template from a JSON object.
This is the core function of the renderEDETemplate handler. Accepts a JSON
object written in a ByteString
and a key to find a compiled EDE template
declared by the compileEDETemplates handler.
renderEDETemplateWith Source #
Arguments
:: (ByteString -> Maybe Value) | Decoding function |
-> HashMap Id Term | Collection of extra filters |
-> ByteString | JSON object |
-> ByteString | Key to find the EDE template |
-> IO ByteString |
Renders an EDE template with custom decoding function and filters.
Choice of the decoding function makes EDE available for templating from any
configuration language that maps to the Aeson's Value
.
renderEDETemplateFromFreeValue Source #
Arguments
:: ByteString | Key to find the EDE template | JSON object |
-> IO ByteString |
Renders an EDE template from a JSON object.
This is the core function of the renderEDETemplateFromFreeValue handler. Accepts a JSON object attached after the search key and a vertical bar such as key|$hs_json.