ngx-export-tools-0.2.1.1: Extra tools for Nginx haskell module

Copyright(c) Alexey Radkov 2018
LicenseBSD-style
Maintaineralexey.radkov@gmail.com
Stabilityexperimental
Portabilitynon-portable (requires Template Haskell)
Safe HaskellNone
LanguageHaskell98

NgxExport.Tools

Contents

Description

Extra tools for using in custom Haskell code with nginx-haskell-module.

Synopsis

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.

ngxNow :: IO CTime Source #

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
Read TimeInterval Source # 
Instance details

Defined in NgxExport.Tools

Show TimeInterval Source # 
Instance details

Defined in NgxExport.Tools

Generic TimeInterval Source # 
Instance details

Defined in NgxExport.Tools

Associated Types

type Rep TimeInterval :: Type -> Type #

Lift TimeInterval Source # 
Instance details

Defined in NgxExport.Tools

Methods

lift :: TimeInterval -> Q Exp #

FromJSON TimeInterval Source # 
Instance details

Defined in NgxExport.Tools

type Rep TimeInterval Source # 
Instance details

Defined in NgxExport.Tools

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 -> IO ByteString

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.Tools

import           Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as C8L
import           Data.Aeson
import           Control.Monad
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 -> IO L.ByteString
testRead = return . C8L.pack . show

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

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

testReadJSON :: (FromJSON a, Show a) => a -> IO L.ByteString
testReadJSON = return . C8L.pack . show

data ConfJSON = ConfJSONCon1 Int
              | ConfJSONCon2 deriving (Generic, Show)
instance FromJSON ConfJSON

testReadConfJSON :: ConfJSON -> Bool -> IO L.ByteString
testReadConfJSON = const . testReadJSON
ngxExportSimpleServiceTypedAsJSON 'testReadConfJSON ''ConfJSON
    SingleShotService

Here five simple services of various types are defined: test, testReadInt, testReadConf, testReadConfWithDelay, and testReadConfJSON. Service testReadInt is not a good example though. The problem is that typed 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 and ConfWithDelay) 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 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:

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 Hr 1), 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.

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 / {
            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";
        }
    }
}

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

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.

newtype CInt #

Haskell type representing the C int type.

Constructors

CInt Int32 
Instances
Bounded CInt 
Instance details

Defined in Foreign.C.Types

Enum CInt 
Instance details

Defined in Foreign.C.Types

Methods

succ :: CInt -> CInt #

pred :: CInt -> CInt #

toEnum :: Int -> CInt #

fromEnum :: CInt -> Int #

enumFrom :: CInt -> [CInt] #

enumFromThen :: CInt -> CInt -> [CInt] #

enumFromTo :: CInt -> CInt -> [CInt] #

enumFromThenTo :: CInt -> CInt -> CInt -> [CInt] #

Eq CInt 
Instance details

Defined in Foreign.C.Types

Methods

(==) :: CInt -> CInt -> Bool #

(/=) :: CInt -> CInt -> Bool #

Integral CInt 
Instance details

Defined in Foreign.C.Types

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

quotRem :: CInt -> CInt -> (CInt, CInt) #

divMod :: CInt -> CInt -> (CInt, CInt) #

toInteger :: CInt -> Integer #

Num CInt 
Instance details

Defined in Foreign.C.Types

Methods

(+) :: CInt -> CInt -> CInt #

(-) :: CInt -> CInt -> CInt #

(*) :: CInt -> CInt -> CInt #

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Ord CInt 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CInt -> CInt -> Ordering #

(<) :: CInt -> CInt -> Bool #

(<=) :: CInt -> CInt -> Bool #

(>) :: CInt -> CInt -> Bool #

(>=) :: CInt -> CInt -> Bool #

max :: CInt -> CInt -> CInt #

min :: CInt -> CInt -> CInt #

Read CInt 
Instance details

Defined in Foreign.C.Types

Real CInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CInt -> Rational #

Show CInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Bits CInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CInt 
Instance details

Defined in Foreign.C.Types

newtype CUInt #

Haskell type representing the C unsigned int type.

Constructors

CUInt Word32 
Instances
Bounded CUInt 
Instance details

Defined in Foreign.C.Types

Enum CUInt 
Instance details

Defined in Foreign.C.Types

Eq CUInt 
Instance details

Defined in Foreign.C.Types

Methods

(==) :: CUInt -> CUInt -> Bool #

(/=) :: CUInt -> CUInt -> Bool #

Integral CUInt 
Instance details

Defined in Foreign.C.Types

Num CUInt 
Instance details

Defined in Foreign.C.Types

Ord CUInt 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CUInt -> CUInt -> Ordering #

(<) :: CUInt -> CUInt -> Bool #

(<=) :: CUInt -> CUInt -> Bool #

(>) :: CUInt -> CUInt -> Bool #

(>=) :: CUInt -> CUInt -> Bool #

max :: CUInt -> CUInt -> CUInt #

min :: CUInt -> CUInt -> CUInt #

Read CUInt 
Instance details

Defined in Foreign.C.Types

Real CUInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CUInt -> Rational #

Show CUInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Bits CUInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CUInt 
Instance details

Defined in Foreign.C.Types