Copyright | (c) Alexey Radkov 2018-2024 |
---|---|
License | BSD-style |
Maintainer | alexey.radkov@gmail.com |
Stability | stable |
Portability | non-portable (requires Template Haskell) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data ServiceMode
- ngxExportSimpleService :: Name -> ServiceMode -> Q [Dec]
- ngxExportSimpleServiceTyped :: Name -> Name -> ServiceMode -> Q [Dec]
- ngxExportSimpleServiceTypedAsJSON :: Name -> 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 are classified as untyped or typed. The untyped services have type
ByteString
->Bool
->IO
ByteString
which corresponds to the type of usual services from module NgxExport. The typed services are backed by functions from module NgxExport.Tools.Read and may have two different types:
Read
a => a ->Bool
->IO
ByteString
FromJSON
a => a ->Bool
->IO
ByteString
The choice of a certain type of a typed service depends on the format in which the typed data will be passed from the Nginx configuration.
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.fromStrictngxExportSimpleService
'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 . testReadngxExportSimpleServiceTyped
'testReadInt ''Int $PersistentService
$ Just $Sec
10 newtype Conf = Conf Int deriving (Read, Show) testReadConf :: Conf -> Bool -> IO L.ByteString testReadConf = const . testReadngxExportSimpleServiceTyped
'testReadConf ''Conf $PersistentService
$ Just $Sec
10 testConfStorage :: ByteString -> IO L.ByteString testConfStorage = const $ showAsLazyByteString <$> readIORef storage_Conf_testReadConfngxExportIOYY
'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 cngxExportSimpleServiceTyped
'testReadConfWithDelay ''ConfWithDelay $PersistentService
Nothing data ConfJSON = ConfJSONCon1 Int | ConfJSONCon2 deriving (Generic, Show) instance FromJSON ConfJSON testReadConfJSON :: ConfJSON -> Bool -> IO L.ByteString testReadConfJSON =ignitionService
testReadngxExportSimpleServiceTypedAsJSON
'testReadConfJSON ''ConfJSONSingleShotService
Here five simple services of various types are defined: test,
testReadInt, testReadConf, testReadConfWithDelay, and
testReadConfJSON. Persistent 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 $Sec
10 - No sleeps between iterations (
)PersistentService
Nothing - Single-shot services (
)SingleShotService
In this contrived example, the most efficient sleeping strategy is a
single-shot service because data is not altered during the 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)
In this example, persistent typed services had a single instance running. But
if there had been multiple instances of a single persistent typed service, we
would have had a problem. Remember that the name of the configuration storage
is made up of the names of the type and the service. This means that multiple
instances of a single persistent typed service share a single configuration
in the runtime which is not what is normally expected. Exporters
ngxExportSimpleServiceTyped'
and ngxExportSimpleServiceTypedAsJSON'
do
not store configurations and are preferable in such cases.
Preloading storages of persistent typed services
Storages of persistent typed services can be preloaded synchronously with
ngxExportInitHook
. This is useful if a storage gets accessed immediately
after the start of processing client requests in a request handler which
expects that the storage has already been initialized (for example, a request
handler may unpack the storage with fromJust
without checking errors).
File test_tools.hs: preload storage_Int_testReadInt
import System.Environment -- ... initTestReadInt :: IO () initTestReadInt = do _ : v : _ <- dropWhile (/= "--testReadInt") <$>getArgs
let i = read v i `seq` writeIORef storage_Int_testReadInt (Just i)ngxExportInitHook
'initTestReadInt
Note that the preloaded value gets evaluated inside the hook to spot any parse errors inplace before the start of processing client requests.
File nginx.conf: read data for storage_Int_testReadInt
haskell program_options --testReadInt 800; # ... haskell_run_service simpleService_testReadInt $hs_testReadInt -;
The preloaded value gets passed in directive haskell program_options. The value in the service declaration can be replaced by any lexeme as it won't be parsed. In this example, it was replaced by a dash.
Exported data and functions
data ServiceMode Source #
Defines a sleeping strategy.
PersistentService (Maybe TimeInterval) | Persistent service (with or without periodical sleeps) |
SingleShotService | Single-shot service |
ngxExportSimpleService Source #
:: Name | Name of the service |
-> ServiceMode | Service mode |
-> Q [Dec] |
Exports a simple service of type
ByteString
->Bool
->IO
ByteString
with specified name and service mode.
ngxExportSimpleServiceTyped Source #
:: Name | Name of the service |
-> Name | Name of the custom type |
-> ServiceMode | Service mode |
-> Q [Dec] |
Exports a simple service of type
Read
a => a ->Bool
->IO
ByteString
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, when the service
mode is a PersistentService
, 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 #
:: Name | Name of the service |
-> Name | Name of the custom type |
-> ServiceMode | Service mode |
-> Q [Dec] |
Exports a simple service of type
FromJSON
a => a ->Bool
->IO
ByteString
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,
when the service mode is a PersistentService
, 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.
ngxExportSimpleServiceTyped' Source #
:: Name | Name of the service |
-> Name | Name of the custom type |
-> ServiceMode | Service mode |
-> Q [Dec] |
Exports a simple service of type
Read
a => a ->Bool
->IO
ByteString
with specified name and service mode.
This exporter is similar to ngxExportSimpleServiceTyped
except it does not
store data in a global storage for persistent services. Use this exporter
when multiple instances of the service with different configurations are
required.
Since: 1.2.5
ngxExportSimpleServiceTypedAsJSON' Source #
:: Name | Name of the service |
-> Name | Name of the custom type |
-> ServiceMode | Service mode |
-> Q [Dec] |
Exports a simple service of type
FromJSON
a => a ->Bool
->IO
ByteString
with specified name and service mode.
This exporter is similar to ngxExportSimpleServiceTypedAsJSON
except it
does not store data in a global storage for persistent services. Use this
exporter when multiple instances of the service with different configurations
are required.
Since: 1.2.5
Type declarations
type NgxExportService Source #
= Bool | First-run flag |
-> IO ByteString |
Allows writing fancier declarations of services.
For example, service signalUpconf in
type Upconf = [Text] signalUpconf :: Upconf ->Bool
->IO
ByteString
signalUpconf =voidHandler'
. mapConcurrently_ getUrlngxExportSimpleServiceTyped
'signalUpconf ''Upconf $PersistentService
Nothing
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
Storable CInt | |
Defined in Foreign.C.Types | |
Bits CInt | |
Defined in Foreign.C.Types (.&.) :: 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 | |
Bounded CInt | |
Enum CInt | |
Ix CInt | |
Num CInt | |
Read CInt | |
Integral CInt | |
Real CInt | |
Defined in Foreign.C.Types toRational :: CInt -> Rational # | |
Show CInt | |
NFData CInt | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq CInt | |
Ord CInt | |
Uniform CInt | |
Defined in System.Random.Internal uniformM :: StatefulGen g m => g -> m CInt # | |
UniformRange CInt | |
Defined in System.Random.Internal |
Haskell type representing the C unsigned int
type.
(The concrete types of Foreign.C.Types are platform-specific.)