| Copyright | (c) Alexey Radkov 2018-2024 |
|---|---|
| License | BSD-style |
| Maintainer | alexey.radkov@gmail.com |
| Stability | stable |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
NgxExport.Tools.Read
Description
Synopsis
- readFromByteString :: Read a => ByteString -> Maybe a
- readFromByteStringAsJSON :: FromJSON a => ByteString -> Maybe a
- readFromByteStringWithRPtr :: Read a => ByteString -> (Ptr (), Maybe a)
- readFromByteStringWithRPtrAsJSON :: FromJSON a => ByteString -> (Ptr (), Maybe a)
- skipRPtr :: ByteString -> ByteString
Reading custom types from ByteStrings
This module provides a number of functions to support typed exchange
between Nginx and Haskell handlers. Functions readFromByteString and
readFromByteStringAsJSON expect serialized values of custom types deriving
or implementing instances of Read and FromJSON respectively. Functions
readFromByteStringWithRPtr and readFromByteStringWithRPtrAsJSON
additionally expect a binary value of a C pointer size marshalled in front
of the value of the custom type. This pointer should correspond to the value
of Nginx variable $_r_ptr.
Below is a simple example.
File test_tools.hs
{-# LANGUAGE TemplateHaskell, DeriveGeneric, TypeApplications #-}
module TestTools where
import NgxExport
import NgxExport.Tools.Read
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as C8L
import Data.Aeson
import GHC.Generics
showAsLazyByteString :: Show a => a -> L.ByteString
showAsLazyByteString = C8L.pack . show
newtype Conf = Conf Int deriving (Read, Show)
data ConfJSON = ConfJSONCon1 Int
| ConfJSONCon2 deriving (Generic, Show)
instance FromJSON ConfJSON
testReadIntHandler :: ByteString -> L.ByteString
testReadIntHandler = showAsLazyByteString .
readFromByteString @Int
ngxExportYY 'testReadIntHandler
testReadConfHandler :: ByteString -> L.ByteString
testReadConfHandler = showAsLazyByteString .
readFromByteString @Conf
ngxExportYY 'testReadConfHandler
testReadConfJSONHandler :: ByteString -> IO L.ByteString
testReadConfJSONHandler = return . showAsLazyByteString .
readFromByteStringAsJSON @ConfJSON
ngxExportAsyncIOYY 'testReadConfJSONHandler
testReadConfWithRPtrHandler :: ByteString -> L.ByteString
testReadConfWithRPtrHandler = showAsLazyByteString .
readFromByteStringWithRPtr @Conf
ngxExportYY 'testReadConfWithRPtrHandler
testReadConfWithRPtrJSONHandler :: ByteString -> L.ByteString
testReadConfWithRPtrJSONHandler = showAsLazyByteString .
readFromByteStringWithRPtrAsJSON @ConfJSON
ngxExportYY 'testReadConfWithRPtrJSONHandler
Here, five Haskell handlers are defined: testReadIntHandler, testReadConfHandler, testReadConfJSONHandler, testReadConfWithRPtrHandler, and testReadConfWithRPtrJSONHandler. Four of them are synchronous and one is asynchronous for the sake of variety.
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.so;
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 testReadIntHandler
$hs_testReadIntHandler
-456;
haskell_run testReadConfHandler
$hs_testReadConfHandler
'Conf 21';
haskell_run_async testReadConfJSONHandler
$hs_testReadConfJSONHandler
'{"tag":"ConfJSONCon2"}';
haskell_run_async testReadConfJSONHandler
$hs_testReadConfJSONHandlerBadInput
'{"tag":"Unknown"}';
haskell_run testReadConfWithRPtrHandler
$hs_testReadConfWithRPtrHandler
'${_r_ptr}Conf 21';
haskell_run testReadConfWithRPtrJSONHandler
$hs_testReadConfWithRPtrJSONHandler
'$_r_ptr
{"tag":"ConfJSONCon1", "contents":4}
';
echo "Handler variables:";
echo " hs_testReadIntHandler: $hs_testReadIntHandler";
echo " hs_testReadConfHandler: $hs_testReadConfHandler";
echo " hs_testReadConfJSONHandler: $hs_testReadConfJSONHandler";
echo " hs_testReadConfJSONHandlerBadInput: $hs_testReadConfJSONHandlerBadInput";
echo " hs_testReadConfWithRPtrHandler: $hs_testReadConfWithRPtrHandler";
echo " hs_testReadConfWithRPtrJSONHandler: $hs_testReadConfWithRPtrJSONHandler";
}
}
}
Handlers that read the pointer to the Nginx request object can also be written in a fancy style as shown below.
haskell_run testReadConfWithRPtrHandler(r)
$hs_testReadConfWithRPtrHandler
'Conf 21';
haskell_run testReadConfWithRPtrJSONHandler(r)
$hs_testReadConfWithRPtrJSONHandler
'{"tag":"ConfJSONCon1", "contents":4}';
A simple test
$ curl 'http://localhost:8010/' Handler variables: hs_testReadIntHandler: Just (-456) hs_testReadConfHandler: Just (Conf 21) hs_testReadConfJSONHandler: Just ConfJSONCon2 hs_testReadConfJSONHandlerBadInput: Nothing hs_testReadConfWithRPtrHandler: (0x00000000016fc790,Just (Conf 21)) hs_testReadConfWithRPtrJSONHandler: (0x00000000016fc790,Just (ConfJSONCon1 4))
Note that non-latin Unicode characters read in constructors of custom types get truncated. Particularly, this means that string literals containing such characters will be garbled.
Exported functions
readFromByteString :: Read a => ByteString -> Maybe a Source #
Reads an object of a custom type implementing an instance of Read
from a ByteString.
Returns Nothing if reading fails.
readFromByteStringAsJSON :: FromJSON a => ByteString -> Maybe a Source #
Reads an object of a custom type implementing an instance of FromJSON
from a ByteString.
Returns Nothing if reading fails.
readFromByteStringWithRPtr :: Read a => ByteString -> (Ptr (), Maybe a) Source #
Reads a pointer to the Nginx request object followed by an object of
a custom type implementing an instance of Read from a ByteString.
Throws an exception if unmarshalling of the request pointer fails. Returns
Nothing in the second element of the tuple if reading of the custom object
fails. Notice that the value of the returned request pointer is not checked
against NULL.
readFromByteStringWithRPtrAsJSON :: FromJSON a => ByteString -> (Ptr (), Maybe a) Source #
Reads a pointer to the Nginx request object followed by an object of
a custom type implementing an instance of FromJSON from a ByteString.
Throws an exception if unmarshalling of the request pointer fails. Returns
Nothing in the second element of the tuple if decoding of the custom object
fails. Notice that the value of the returned request pointer is not checked
against NULL.
skipRPtr :: ByteString -> ByteString Source #
Skips the number of bytes equal to the size of a pointer from the beginning
of a ByteString.
This can be useful to drop a pointer to the Nginx request object passed at the beginning of a handler's argument.