| Copyright | (c) Alexey Radkov 2018 |
|---|---|
| License | BSD-style |
| Maintainer | alexey.radkov@gmail.com |
| Stability | experimental |
| Portability | non-portable (requires Template Haskell) |
| Safe Haskell | None |
| Language | Haskell98 |
NgxExport.Tools
Contents
Description
Extra tools for using in custom Haskell code with nginx-haskell-module.
Synopsis
- exitWorkerProcess :: IO ()
- terminateWorkerProcess :: IO ()
- ngxRequestPtr :: ByteString -> Ptr ()
- ngxNow :: IO CTime
- data TimeInterval
- toSec :: TimeInterval -> Int
- threadDelaySec :: Int -> IO ()
- 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)
- data ServiceMode
- ngxExportSimpleService :: Name -> ServiceMode -> Q [Dec]
- ngxExportSimpleServiceTyped :: Name -> Name -> ServiceMode -> Q [Dec]
- ngxExportSimpleServiceTypedAsJSON :: Name -> Name -> ServiceMode -> Q [Dec]
- newtype CInt = CInt Int32
- newtype CUInt = CUInt Word32
Various useful functions and data
exitWorkerProcess :: IO () Source #
Terminates current Nginx worker process.
Nginx master process shall spawn a new worker process thereafter.
terminateWorkerProcess :: IO () Source #
Terminates current Nginx worker process.
Nginx master process shall not spawn a new worker process thereafter.
ngxRequestPtr :: ByteString -> Ptr () Source #
Unmarshals the value of Nginx variable $_r_ptr into a pointer to the Nginx request object.
This is safe to use in request-based Haskell handlers such as synchronous and asynchronous tasks and content handlers, but not in services and their derivatives. In asynchronous tasks and content handlers the value must be used as read-only. The value can be passed into a C plugin, however, as opposed to usual functions in Nginx C code, it must be tested against the NULL value.
Returns current time as the number of seconds elapsed since UNIX epoch.
The value is taken from Nginx core, so no additional system calls get
involved. On the other hand, it means that this is only safe to use from
an Nginx worker's main thread, i.e. in synchronous Haskell handlers and
service hooks. Be also aware that this is a small type casting hack:
the value is interpreted as being of type time_t while having been
actually wrapped in a bigger C struct as its first element.
Time intervals
data TimeInterval Source #
Time intervals.
Constructors
| Hr Int | Hours |
| Min Int | Minutes |
| Sec Int | Seconds |
| HrMin Int Int | Hours and minutes |
| MinSec Int Int | Minutes and seconds |
Instances
toSec :: TimeInterval -> Int Source #
Converts a time interval into seconds.
threadDelaySec :: Int -> IO () Source #
Delays current thread for the specified number of seconds.
Reading custom types from ByteStrings
There are a number of functions to support typed exchange between Nginx
and Haskell handlers. Functions readFromByteString and
readFromByteStringAsJSON expect values of custom types deriving from
Read and FromJSON respectively. Functions readFromByteStringWithRPtr
and readFromByteStringWithRPtrAsJSON additionally expect a binary value
of a C pointer size marshalled at the beginning of their arguments before
the value of the custom type. This pointer should correspond to the value
of Nginx variable $_r_ptr.
Below is a toy example.
File test_tools.hs.
{-# LANGUAGE TemplateHaskell, DeriveGeneric #-}
module TestTools where
import NgxExport
import NgxExport.Tools
import Foreign.Ptr
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 :: ByteString -> Maybe Int)
ngxExportYY 'testReadIntHandler
testReadConfHandler :: ByteString -> L.ByteString
testReadConfHandler = showAsLazyByteString .
(readFromByteString :: ByteString -> Maybe Conf)
ngxExportYY 'testReadConfHandler
testReadConfJSONHandler :: ByteString -> IO L.ByteString
testReadConfJSONHandler = return . showAsLazyByteString .
(readFromByteStringAsJSON :: ByteString -> Maybe ConfJSON)
ngxExportAsyncIOYY 'testReadConfJSONHandler
testReadConfWithRPtrHandler :: ByteString -> L.ByteString
testReadConfWithRPtrHandler = showAsLazyByteString .
(readFromByteStringWithRPtr :: ByteString -> (Ptr (), Maybe Conf))
ngxExportYY 'testReadConfWithRPtrHandler
testReadConfWithRPtrJSONHandler :: ByteString -> L.ByteString
testReadConfWithRPtrJSONHandler = showAsLazyByteString .
(readFromByteStringWithRPtrAsJSON :: ByteString -> (Ptr (), Maybe 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";
}
}
}
Let's run 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))
readFromByteString :: Read a => ByteString -> Maybe a Source #
Reads an object of a custom type deriving Read from a ByteString.
Returns Nothing if reading fails.
readFromByteStringAsJSON :: FromJSON a => ByteString -> Maybe a Source #
Reads an object of a custom type deriving 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 deriving Read from a ByteString.
Throws an exception if unmarshalling of the request pointer fails. In the
second element of the tuple returns Nothing 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 deriving FromJSON from a ByteString.
Throws an exception if unmarshalling of the request pointer fails. In the
second element of the tuple returns Nothing if decoding of the custom
object fails. Notice that the value of the returned request pointer is not
checked against NULL.
Exporters of simple services
There are a number of exporters for simple services. Here simplicity means avoiding boilerplate code regarding to efficient reading of typed configurations and timed restarts of services. All simple services have type
ByteString->Bool->IOByteString
which corresponds to the type of usual services from module NgxExport.
Below is a toy example.
File test_tools.hs.
{-# LANGUAGE TemplateHaskell, DeriveGeneric, RecordWildCards #-}
module TestTools where
import NgxExport
import NgxExport.Tools
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as C8L
import Data.Aeson
import Data.IORef
import Control.Monad
import GHC.Generics
test :: ByteString -> Bool -> IO L.ByteString
test = const . return . L.fromStrict
ngxExportSimpleService 'test $
PersistentService $ Just $ Sec 10
showAsLazyByteString :: Show a => a -> L.ByteString
showAsLazyByteString = C8L.pack . show
testRead :: Show a => a -> IO L.ByteString
testRead = return . showAsLazyByteString
testReadInt :: Int -> Bool -> IO L.ByteString
testReadInt = const . testRead
ngxExportSimpleServiceTyped 'testReadInt ''Int $
PersistentService $ Just $ Sec 10
newtype Conf = Conf Int deriving (Read, Show)
testReadConf :: Conf -> Bool -> IO L.ByteString
testReadConf = const . testRead
ngxExportSimpleServiceTyped 'testReadConf ''Conf $
PersistentService $ Just $ Sec 10
testConfStorage :: ByteString -> IO L.ByteString
testConfStorage = const $
showAsLazyByteString <$> readIORef storage_Conf_testReadConf
ngxExportIOYY 'testConfStorage
data ConfWithDelay = ConfWithDelay { delay :: TimeInterval
, value :: Int
} deriving (Read, Show)
testReadConfWithDelay :: ConfWithDelay -> Bool -> IO L.ByteString
testReadConfWithDelay c@ConfWithDelay {..} fstRun = do
unless fstRun $ threadDelaySec $ toSec delay
testRead c
ngxExportSimpleServiceTyped 'testReadConfWithDelay ''ConfWithDelay $
PersistentService Nothing
data ConfJSON = ConfJSONCon1 Int
| ConfJSONCon2 deriving (Generic, Show)
instance FromJSON ConfJSON
testReadConfJSON :: ConfJSON -> IO L.ByteString
testReadConfJSON = testRead
ngxExportSimpleServiceTypedAsJSON 'testReadConfJSON ''ConfJSON
SingleShotService
Here five simple services of various types are defined: test,
testReadInt, testReadConf, testReadConfWithDelay, and
testReadConfJSON. Typed services hold IORef storages to save their
configurations for faster access in future iterations. The name of a storage
consists of the name of its type and the name of the service connected by an
underscore and prefixed as a whole word with storage_.
As soon as all the services in the example merely echo their configurations
into their service variables, they must sleep for a while between iterations.
Sleeps are managed by strategies defined in type ServiceMode. There are
basically three sleeping strategies:
- Periodical sleeps (for example,
)PersistentService$ Just $Sec10 - No sleeps between iterations (
)PersistentServiceNothing - Single-shot services (
)SingleShotService
In this toy example the most efficient sleeping strategy is a single-shot
service because data is not altered during runtime. Under the hood, the
single-shot strategy is implemented as periodical sleeps (with period of
), except it runs the handler only on the first iteration, while
afterwards it merely returns empty values: as such, this strategy should be
accompanied by Nginx directive haskell_service_var_ignore_empty.Hr 1
Notice that service testReadConfWithDelay manages time delays on its own,
therefore it uses no-sleeps strategy .PersistentService Nothing
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;
haskell_run_service simpleService_test
$hs_test
test;
haskell_run_service simpleService_testReadInt
$hs_testReadInt
5000000;
haskell_run_service simpleService_testReadConf
$hs_testReadConf
'Conf 20';
haskell_run_service simpleService_testReadConfWithDelay
$hs_testReadConfWithDelay
'ConfWithDelay { delay = Sec 10, value = 12 }';
haskell_run_service simpleService_testReadConfJSON
$hs_testReadConfJSON
'{"tag":"ConfJSONCon1", "contents":56}';
haskell_service_var_ignore_empty $hs_testReadConfJSON;
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 testConfStorage $hs_testConfStorage '';
echo "Service variables:";
echo " hs_test: $hs_test";
echo " hs_testReadInt: $hs_testReadInt";
echo " hs_testReadConf: $hs_testReadConf";
echo " hs_testReadConfWithDelay: $hs_testReadConfWithDelay";
echo " hs_testReadConfJSON: $hs_testReadConfJSON";
echo "Storages of service variables:";
echo " hs_testConfStorage: $hs_testConfStorage";
}
}
}
Notice that Haskel handlers defined in test_tools.hs are referred from the Nginx configuration file with prefix simpleService_.
Let's run a simple test.
$ curl 'http://localhost:8010/'
Service variables:
hs_test: test
hs_testReadInt: 5000000
hs_testReadConf: Conf 20
hs_testReadConfWithDelay: ConfWithDelay {delay = Sec 10, value = 12}
hs_testReadConfJSON: ConfJSONCon1 56
Storages of service variables:
hs_testConfStorage: Just (Conf 20)data ServiceMode Source #
Defines a sleeping strategy.
Single-shot services should be accompanied by Nginx directive haskell_service_var_ignore_empty.
Constructors
| PersistentService (Maybe TimeInterval) | Persistent service (with or without periodical sleeps) |
| SingleShotService | Single-shot service |
ngxExportSimpleService Source #
Arguments
| :: Name | Name of the service |
| -> ServiceMode | Service mode |
| -> Q [Dec] |
Exports a simple service of type
ByteString->Bool->IOByteString
or (when service mode is SingleShotService)
ByteString->IOByteString
with specified name and service mode.
ngxExportSimpleServiceTyped Source #
Arguments
| :: Name | Name of the service |
| -> Name | Name of the custom type |
| -> ServiceMode | Service mode |
| -> Q [Dec] |
Exports a simple service of type
Reada => a ->Bool->IOByteString
or (when service mode is SingleShotService)
Reada => a ->IOByteString
with specified name and service mode.
The service expects an object of a custom type deriving Read as its
first argument. For the sake of efficiency, this object gets deserialized
into a global IORef data storage on the first service run to be further
accessed directly from this storage. The storage can be accessed from
elsewhere by a name comprised of the name of the custom type and the name of
the service connected by an underscore and prefixed as a whole word with
storage_. The stored data is wrapped in Maybe container.
When reading of the custom object fails on the first service run, the
service terminates the worker process using terminateWorkerProcess.
ngxExportSimpleServiceTypedAsJSON Source #
Arguments
| :: Name | Name of the service |
| -> Name | Name of the custom type |
| -> ServiceMode | Service mode |
| -> Q [Dec] |
Exports a simple service of type
FromJSONa => a ->Bool->IOByteString
or (when service mode is SingleShotService)
FromJSONa => a ->IOByteString
with specified name and service mode.
The service expects an object of a custom type deriving FromJSON as its
first argument. For the sake of efficiency, this object gets deserialized
into a global IORef data storage on the first service run to be further
accessed directly from this storage. The storage can be accessed from
elsewhere by a name comprised of the name of the custom type and the name of
the service connected by an underscore and prefixed as a whole word with
storage_. The stored data is wrapped in Maybe container.
When reading of the custom object fails on the first service run, the
service terminates the worker process using terminateWorkerProcess.
Re-exported data constructors from Foreign.C
Re-exports are needed by exporters for marshalling in foreign calls.
Haskell type representing the C int type.
Instances
| Bounded CInt | |
| Enum CInt | |
| Eq CInt | |
| Integral CInt | |
| Num CInt | |
| Ord CInt | |
| Read CInt | |
| Real CInt | |
Defined in Foreign.C.Types Methods toRational :: CInt -> Rational # | |
| Show CInt | |
| Storable CInt | |
Defined in Foreign.C.Types | |
| Bits CInt | |
Defined in Foreign.C.Types Methods (.&.) :: CInt -> CInt -> CInt # (.|.) :: CInt -> CInt -> CInt # complement :: CInt -> CInt # shift :: CInt -> Int -> CInt # rotate :: CInt -> Int -> CInt # setBit :: CInt -> Int -> CInt # clearBit :: CInt -> Int -> CInt # complementBit :: CInt -> Int -> CInt # testBit :: CInt -> Int -> Bool # bitSizeMaybe :: CInt -> Maybe Int # shiftL :: CInt -> Int -> CInt # unsafeShiftL :: CInt -> Int -> CInt # shiftR :: CInt -> Int -> CInt # unsafeShiftR :: CInt -> Int -> CInt # rotateL :: CInt -> Int -> CInt # | |
| FiniteBits CInt | |
Defined in Foreign.C.Types Methods finiteBitSize :: CInt -> Int # countLeadingZeros :: CInt -> Int # countTrailingZeros :: CInt -> Int # | |
Haskell type representing the C unsigned int type.
Instances
| Bounded CUInt | |
| Enum CUInt | |
Defined in Foreign.C.Types | |
| Eq CUInt | |
| Integral CUInt | |
| Num CUInt | |
| Ord CUInt | |
| Read CUInt | |
| Real CUInt | |
Defined in Foreign.C.Types Methods toRational :: CUInt -> Rational # | |
| Show CUInt | |
| Storable CUInt | |
| Bits CUInt | |
Defined in Foreign.C.Types Methods (.&.) :: CUInt -> CUInt -> CUInt # (.|.) :: CUInt -> CUInt -> CUInt # xor :: CUInt -> CUInt -> CUInt # complement :: CUInt -> CUInt # shift :: CUInt -> Int -> CUInt # rotate :: CUInt -> Int -> CUInt # setBit :: CUInt -> Int -> CUInt # clearBit :: CUInt -> Int -> CUInt # complementBit :: CUInt -> Int -> CUInt # testBit :: CUInt -> Int -> Bool # bitSizeMaybe :: CUInt -> Maybe Int # shiftL :: CUInt -> Int -> CUInt # unsafeShiftL :: CUInt -> Int -> CUInt # shiftR :: CUInt -> Int -> CUInt # unsafeShiftR :: CUInt -> Int -> CUInt # rotateL :: CUInt -> Int -> CUInt # | |
| FiniteBits CUInt | |
Defined in Foreign.C.Types Methods finiteBitSize :: CUInt -> Int # countLeadingZeros :: CUInt -> Int # countTrailingZeros :: CUInt -> Int # | |