| Copyright | (c) Alexey Radkov 2018-2023 |
|---|---|
| License | BSD-style |
| Maintainer | alexey.radkov@gmail.com |
| Stability | stable |
| Portability | non-portable (requires Template Haskell) |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
NgxExport.Tools.SimpleService
Description
Synopsis
- data ServiceMode
- ngxExportSimpleService :: Name -> ServiceMode -> Q [Dec]
- ngxExportSimpleServiceTyped :: Name -> Name -> ServiceMode -> Q [Dec]
- ngxExportSimpleServiceTypedAsJSON :: Name -> Name -> ServiceMode -> Q [Dec]
- type NgxExportService = Bool -> IO ByteString
- newtype CInt = CInt Int32
- newtype CUInt = CUInt Word32
Exporters of simple services
This module implements 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 simple 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 -> Bool -> IO L.ByteString
testReadConfJSON = ignitionService 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. A single-shot service
runs exactly two times during the lifetime of a worker process: the first
run (when the second argument of the service, i.e. the first-run flag, is
True) is immediately followed by the second run (when the first-run flag
is False). On the second run the service handler is used as an exception
handler when the service is shutting down after the WorkerProcessIsExiting
exception has been thrown. Accordingly, a single-shot handler can be used
for allocation of some global resources (when the first-run flag is True),
and cleaning them up (when the first-run flag is False).
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}';
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_.
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)Exported data and functions
data ServiceMode Source #
Defines a sleeping strategy.
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
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
with specified name and service mode.
The service expects an object of a custom type implementing an instance of
Read at 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 a Maybe container which
contains Nothing until the initialization on the first service run.
When reading of the custom object fails on the first service run, the
service terminates the worker process by calling terminateWorkerProcess
with a corresponding message.
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
with specified name and service mode.
The service expects an object of a custom type implementing an instance of
FromJSON at 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 a Maybe
container which contains Nothing until the initialization on the first
service run.
When reading of the custom object fails on the first service run, the
service terminates the worker process by calling terminateWorkerProcess
with a corresponding message.
Type declarations
type NgxExportService Source #
Arguments
| = Bool | First-run flag |
| -> IO ByteString |
Allows writing fancier declarations of services.
For example, service signalUpconf in
type Upconf = [Text] signalUpconf :: Upconf ->Bool->IOByteStringsignalUpconf =voidHandler'. mapConcurrently_ getUrlngxExportSimpleServiceTyped'signalUpconf ''Upconf $PersistentServiceNothing
can be rewritten in a fancier way:
signalUpconf :: Upconf -> NgxExportService
signalUpconf = voidHandler' . mapConcurrently_ getUrl
Since: 1.2.2
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.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned int type.
(The concrete types of Foreign.C.Types are platform-specific.)