| 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
- 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 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. 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
readFromByteString :: Read a => ByteString -> Maybe a Source #
Reads a custom type deriving Read from a ByteString.
Returns Nothing if reading fails.
readFromByteStringAsJSON :: FromJSON a => ByteString -> Maybe a Source #
Reads a custom type deriving FromJSON from a ByteString.
Returns Nothing if reading fails.
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 #-}
module TestTools where
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 GHC.Generics
test :: ByteString -> Bool -> IO L.ByteString
test = const . return . L.fromStrict
ngxExportSimpleService 'test $
PersistentService $ Just $ Sec 10
testRead :: (Read a, Show a) => a -> Bool -> IO L.ByteString
testRead = const . return . C8L.pack . show
testReadInt :: Int -> Bool -> IO L.ByteString
testReadInt = testRead
ngxExportSimpleServiceTyped 'testReadInt ''Int $
PersistentService $ Just $ Sec 10
newtype Conf = Conf Int deriving (Read, Show)
testReadConf :: Conf -> Bool -> IO L.ByteString
testReadConf = testRead
ngxExportSimpleServiceTyped 'testReadConf ''Conf $
PersistentService $ Just $ Sec 10
testReadJSON :: (FromJSON a, Show a) => a -> Bool -> IO L.ByteString
testReadJSON = const . return . C8L.pack . show
data ConfJSON = ConfJSONCon1 Int
| ConfJSONCon2 deriving (Generic, Show)
instance FromJSON ConfJSON
testReadConfJSON :: ConfJSON -> Bool -> IO L.ByteString
testReadConfJSON = testReadJSON
ngxExportSimpleServiceTypedAsJSON 'testReadConfJSON ''ConfJSON
SingleShotService
Here four simple services of various types are defined: test,
testReadInt, testReadConf, and testReadConfJSON. Service testReadInt
is not a good example though. The problem is that simple services build
IORef storages to save their configurations for faster access in future
iterations. The name of a storage consists of the name of its type prefixed
with storage_, which means that it's wiser to use custom types or
wrappers of well-known types (such as Conf) in order to avoid exhaustion
of top-level names. In general, this also means that it's not possible to
declare in a single Nginx configuration script two or more typed simple
services with identical names of their configuration types.
As soon as all the services in the example merely echo their arguments 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
All the services in the example ignore their second parameter (of type
Bool) which denotes the first run of the service.
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_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 / {
echo "Service variables:";
echo " hs_test: $hs_test";
echo " hs_testReadInt: $hs_testReadInt";
echo " hs_testReadConf: $hs_testReadConf";
echo " hs_testReadConfJSON: $hs_testReadConfJSON";
}
}
}
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_testReadConfJSON: ConfJSONCon1 56
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 with specified name and service mode.
The service expects a plain ByteString object as its first argument.
ngxExportSimpleServiceTyped Source #
Arguments
| :: Name | Name of the service |
| -> Name | Name of the custom type |
| -> ServiceMode | Service mode |
| -> Q [Dec] |
Exports a simple service 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 name comprised of the name of the custom type prefixed with
storage_. The stored data is wrapped in Maybe container.
ngxExportSimpleServiceTypedAsJSON Source #
Arguments
| :: Name | Name of the service |
| -> Name | Name of the custom type |
| -> ServiceMode | Service mode |
| -> Q [Dec] |
Exports a simple service 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 name comprised of the name of the custom type prefixed with
storage_. The stored data is wrapped in Maybe container.
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 # | |