Copyright | (c) Alexey Radkov 2016-2021 |
---|---|
License | BSD-style |
Maintainer | alexey.radkov@gmail.com |
Stability | stable |
Portability | non-portable (requires POSIX and Template Haskell) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
NgxExport
Description
Nginx / Haskell interoperability layer and exporters of regular Haskell functions at Nginx level for using in configuration directives of nginx-haskell-module.
Synopsis
- type ContentHandlerResult = (ByteString, ByteString, Int, HTTPHeaders)
- type UnsafeContentHandlerResult = (ByteString, ByteString, Int)
- type HTTPHeaders = [(ByteString, ByteString)]
- ngxExportSS :: Name -> Q [Dec]
- ngxExportSSS :: Name -> Q [Dec]
- ngxExportSLS :: Name -> Q [Dec]
- ngxExportBS :: Name -> Q [Dec]
- ngxExportBSS :: Name -> Q [Dec]
- ngxExportBLS :: Name -> Q [Dec]
- ngxExportYY :: Name -> Q [Dec]
- ngxExportBY :: Name -> Q [Dec]
- ngxExportIOYY :: Name -> Q [Dec]
- ngxExportAsyncIOYY :: Name -> Q [Dec]
- ngxExportAsyncOnReqBody :: Name -> Q [Dec]
- ngxExportServiceIOYY :: Name -> Q [Dec]
- ngxExportHandler :: Name -> Q [Dec]
- ngxExportDefHandler :: Name -> Q [Dec]
- ngxExportUnsafeHandler :: Name -> Q [Dec]
- ngxExportAsyncHandler :: Name -> Q [Dec]
- ngxExportAsyncHandlerOnReqBody :: Name -> Q [Dec]
- ngxExportServiceHook :: Name -> Q [Dec]
- ngxCyclePtr :: IO (Ptr ())
- ngxUpstreamMainConfPtr :: IO (Ptr ())
- ngxCachedTimePtr :: IO (Ptr (Ptr ()))
- ngxCachedPid :: IO CPid
- newtype TerminateWorkerProcess = TerminateWorkerProcess String
- newtype RestartWorkerProcess = RestartWorkerProcess String
- data WorkerProcessIsExiting
- data FinalizeHTTPRequest = FinalizeHTTPRequest Int (Maybe String)
- newtype CInt = CInt Int32
- newtype CUInt = CUInt Word32
Type declarations
type ContentHandlerResult = (ByteString, ByteString, Int, HTTPHeaders) Source #
The 4-tuple contains (content, content-type, HTTP-status, response-headers).
type UnsafeContentHandlerResult = (ByteString, ByteString, Int) Source #
The 3-tuple contains (content, content-type, HTTP-status).
Both the content and the content-type are supposed to be referring to low-level string literals that do not need to be freed upon an HTTP request termination and must not be garbage-collected in the Haskell RTS.
type HTTPHeaders = [(ByteString, ByteString)] Source #
A list of HTTP headers comprised of name-value pairs.
Exporters
Synchronous handlers
Asynchronous handlers and services
ngxExportAsyncOnReqBody :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->ByteString
->IO
ByteString
for using in directive haskell_run_async_on_request_body.
The first argument of the exported function contains buffers of the client request body.
ngxExportServiceIOYY :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->Bool
->IO
ByteString
for using in directives haskell_run_service and haskell_service_var_update_callback.
The boolean argument of the exported function marks that the service is being run for the first time.
Content handlers
ngxExportHandler :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->ContentHandlerResult
for using in directives haskell_content and haskell_static_content.
ngxExportDefHandler :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->ByteString
for using in directives haskell_content and haskell_static_content.
ngxExportUnsafeHandler :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->UnsafeContentHandlerResult
for using in directive haskell_unsafe_content.
ngxExportAsyncHandler :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->IO
ContentHandlerResult
for using in directive haskell_async_content.
ngxExportAsyncHandlerOnReqBody :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->ByteString
->IO
ContentHandlerResult
for using in directive haskell_async_content_on_request_body.
The first argument of the exported function contains buffers of the client request body.
Service hooks
ngxExportServiceHook :: Name -> Q [Dec] Source #
Exports a function of type
ByteString
->IO
ByteString
for using in directives haskell_service_hook and haskell_service_update_hook.
Accessing Nginx global objects
Opaque pointers
ngxCyclePtr :: IO (Ptr ()) Source #
Returns an opaque pointer to the Nginx cycle object for using it in C plugins.
The actual type of the returned pointer is
ngx_cycle_t *
(the value of argument cycle in the worker's initialization function).
ngxUpstreamMainConfPtr :: IO (Ptr ()) Source #
Returns an opaque pointer to the Nginx upstream main configuration for using it in C plugins.
The actual type of the returned pointer is
ngx_http_upstream_main_conf_t *
(the value of expression
ngx_http_cycle_get_module_main_conf(cycle, ngx_http_upstream_module)
in
the worker's initialization function).
ngxCachedTimePtr :: IO (Ptr (Ptr ())) Source #
Returns an opaque pointer to the Nginx cached time object for using it in C plugins.
The actual type of the returned pointer is
volatile ngx_time_t **
(the address of the Nginx global variable ngx_cached_time).
Be aware that time gotten from this pointer is not reliable in asynchronous tasks and services as soon as it gets updated only when some event happens inside the Nginx worker to which the task is bound and thus can be heavily outdated.
Primitive objects
ngxCachedPid :: IO CPid Source #
Returns the PID of the current worker process cached in Nginx.
Since: 1.7.1
Accessing Nginx core functionality from Haskell handlers
newtype TerminateWorkerProcess Source #
Terminates the worker process.
Being thrown from a service, this exception makes Nginx log the supplied message and terminate the worker process without respawning. This can be useful when the service is unable to read its configuration from the Nginx configuration script or to perform an important initialization action.
Since: 1.6.2
Constructors
TerminateWorkerProcess String | Contains the message to log |
Instances
Exception TerminateWorkerProcess Source # | |
Defined in NgxExport | |
Show TerminateWorkerProcess Source # | |
Defined in NgxExport Methods showsPrec :: Int -> TerminateWorkerProcess -> ShowS # show :: TerminateWorkerProcess -> String # showList :: [TerminateWorkerProcess] -> ShowS # | |
Eq TerminateWorkerProcess Source # | |
Defined in NgxExport Methods (==) :: TerminateWorkerProcess -> TerminateWorkerProcess -> Bool # (/=) :: TerminateWorkerProcess -> TerminateWorkerProcess -> Bool # |
newtype RestartWorkerProcess Source #
Restarts the worker process.
The same as TerminateWorkerProcess
, except that a new worker process shall
be spawned by the Nginx master process in place of the current one.
Since: 1.6.3
Constructors
RestartWorkerProcess String | Contains the message to log |
Instances
Exception RestartWorkerProcess Source # | |
Defined in NgxExport Methods toException :: RestartWorkerProcess -> SomeException # fromException :: SomeException -> Maybe RestartWorkerProcess # | |
Show RestartWorkerProcess Source # | |
Defined in NgxExport Methods showsPrec :: Int -> RestartWorkerProcess -> ShowS # show :: RestartWorkerProcess -> String # showList :: [RestartWorkerProcess] -> ShowS # | |
Eq RestartWorkerProcess Source # | |
Defined in NgxExport Methods (==) :: RestartWorkerProcess -> RestartWorkerProcess -> Bool # (/=) :: RestartWorkerProcess -> RestartWorkerProcess -> Bool # |
data WorkerProcessIsExiting Source #
Signals that the worker process is exiting.
This asynchronous exception is thrown from the Nginx core to all services
with cancelWith
when the working process is exiting. An exception handler
that catches this exception is expected to perform the service's specific
cleanup and finalization actions.
Since: 1.6.4
Instances
Exception WorkerProcessIsExiting Source # | |
Defined in NgxExport | |
Show WorkerProcessIsExiting Source # | |
Defined in NgxExport Methods showsPrec :: Int -> WorkerProcessIsExiting -> ShowS # show :: WorkerProcessIsExiting -> String # showList :: [WorkerProcessIsExiting] -> ShowS # | |
Eq WorkerProcessIsExiting Source # | |
Defined in NgxExport Methods (==) :: WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool # (/=) :: WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool # |
data FinalizeHTTPRequest Source #
Finalizes the HTTP request.
Being thrown from an asynchronous variable handler, this exception makes Nginx finalize the current HTTP request with the supplied HTTP status and an optional body. If the body is Nothing then the response will be styled by the Nginx core.
Since: 1.6.3
Constructors
FinalizeHTTPRequest Int (Maybe String) | Contains HTTP status and body |
Instances
Exception FinalizeHTTPRequest Source # | |
Defined in NgxExport Methods toException :: FinalizeHTTPRequest -> SomeException # fromException :: SomeException -> Maybe FinalizeHTTPRequest # | |
Show FinalizeHTTPRequest Source # | |
Defined in NgxExport Methods showsPrec :: Int -> FinalizeHTTPRequest -> ShowS # show :: FinalizeHTTPRequest -> String # showList :: [FinalizeHTTPRequest] -> ShowS # | |
Eq FinalizeHTTPRequest Source # | |
Defined in NgxExport Methods (==) :: FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool # (/=) :: FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool # |
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 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 # | |
Bounded CInt | |
Enum CInt | |
Ix CInt | |
Num CInt | |
Read CInt | |
Integral CInt | |
Real CInt | |
Defined in Foreign.C.Types Methods toRational :: CInt -> Rational # | |
Show CInt | |
NFData CInt | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq CInt | |
Ord CInt | |
Haskell type representing the C unsigned int
type.
(The concrete types of Foreign.C.Types are platform-specific.)