{-# LANGUAGE TemplateHaskell, ForeignFunctionInterface, InterruptibleFFI #-}
{-# LANGUAGE ViewPatterns, PatternSynonyms, TupleSections #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  NgxExport
-- Copyright   :  (c) Alexey Radkov 2016-2019
-- License     :  BSD-style
--
-- Maintainer  :  alexey.radkov@gmail.com
-- Stability   :  stable
-- Portability :  non-portable (requires POSIX)
--
-- Export regular haskell functions for using in directives of
-- <http://github.com/lyokha/nginx-haskell-module nginx-haskell-module>.
--
-----------------------------------------------------------------------------

module NgxExport (
    -- * Type declarations
                  ContentHandlerResult
                 ,UnsafeContentHandlerResult
                 ,HTTPHeaders
    -- * Exporters
    -- *** Synchronous handlers
                 ,ngxExportSS
                 ,ngxExportSSS
                 ,ngxExportSLS
                 ,ngxExportBS
                 ,ngxExportBSS
                 ,ngxExportBLS
                 ,ngxExportYY
                 ,ngxExportBY
                 ,ngxExportIOYY
    -- *** Asynchronous handlers and services
                 ,ngxExportAsyncIOYY
                 ,ngxExportAsyncOnReqBody
                 ,ngxExportServiceIOYY
    -- *** Content handlers
                 ,ngxExportHandler
                 ,ngxExportDefHandler
                 ,ngxExportUnsafeHandler
                 ,ngxExportAsyncHandler
                 ,ngxExportAsyncHandlerOnReqBody
    -- *** Service hooks
                 ,ngxExportServiceHook
    -- * Accessing Nginx global objects
    -- *** Opaque pointers
                 ,ngxCyclePtr
                 ,ngxUpstreamMainConfPtr
                 ,ngxCachedTimePtr
    -- *** Primitive objects
                 ,ngxCachedPid
    -- * Accessing Nginx core functionality from Haskell handlers
                 ,TerminateWorkerProcess (..)
                 ,RestartWorkerProcess (..)
                 ,WorkerProcessIsExiting
                 ,FinalizeHTTPRequest (..)
    -- * Re-exported data constructors from /Foreign.C/
    -- | Re-exports are needed by exporters for marshalling in foreign calls.
                 ,Foreign.C.CInt (..)
                 ,Foreign.C.CUInt (..)
                 ) where

import           Language.Haskell.TH
import           Foreign.C
import           Foreign.Ptr
import           Foreign.StablePtr
import           Foreign.Storable
import           Foreign.Marshal.Alloc
import           Foreign.Marshal.Utils
import           Data.IORef
import           System.IO.Unsafe
import           System.IO.Error
import           System.Posix.IO
import           System.Posix.Types
import           System.Posix.Signals hiding (Handler)
import           System.Posix.Internals
import           Control.Monad
import           Control.Monad.Loops
import           Control.DeepSeq
import qualified Control.Exception as E
import           Control.Exception hiding (Handler)
import           GHC.IO.Exception (ioe_errno)
import           GHC.IO.Device (SeekMode (..))
import           Control.Concurrent.Async
import qualified Data.ByteString as B
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as C8L
import           Data.Binary.Put
import           Data.Bits
import           Paths_ngx_export (version)
import           Data.Version

#if MIN_VERSION_template_haskell(2,11,0)
#define EXTRA_WILDCARD_BEFORE_CON _
#else
#define EXTRA_WILDCARD_BEFORE_CON
#endif

#if MIN_TOOL_VERSION_ghc(8,0,1)
pattern I :: (Num i, Integral a) => i -> a
#endif
pattern $mI :: forall r i a.
(Num i, Integral a) =>
a -> (i -> r) -> (Void# -> r) -> r
I i <- (fromIntegral -> i)
#if MIN_TOOL_VERSION_ghc(8,2,1)
{-# COMPLETE I :: CInt #-}
#endif

#if MIN_TOOL_VERSION_ghc(8,0,1)
pattern PtrLen :: Num l => Ptr s -> l -> (Ptr s, Int)
#endif
pattern $mPtrLen :: forall r l s.
Num l =>
(Ptr s, Int) -> (Ptr s -> l -> r) -> (Void# -> r) -> r
PtrLen s l <- (s, I l)

#if MIN_TOOL_VERSION_ghc(8,0,1)
pattern ToBool :: (Num i, Eq i) => Bool -> i
#endif
pattern $mToBool :: forall r i. (Num i, Eq i) => i -> (Bool -> r) -> (Void# -> r) -> r
ToBool i <- (toBool -> i)
#if MIN_TOOL_VERSION_ghc(8,2,1)
{-# COMPLETE ToBool :: CUInt #-}
#endif

-- | The /4-tuple/ contains
--   /(content, content-type, HTTP-status, response-headers)/.
type ContentHandlerResult = (L.ByteString, B.ByteString, Int, HTTPHeaders)

-- | 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 UnsafeContentHandlerResult = (B.ByteString, B.ByteString, Int)

-- | A list of HTTP headers comprised of /name-value/ pairs.
type HTTPHeaders = [(B.ByteString, B.ByteString)]

data NgxExport = SS              (String -> String)
               | SSS             (String -> String -> String)
               | SLS             ([String] -> String)
               | BS              (String -> Bool)
               | BSS             (String -> String -> Bool)
               | BLS             ([String] -> Bool)
               | YY              (B.ByteString -> L.ByteString)
               | BY              (B.ByteString -> Bool)
               | IOYY            (B.ByteString -> Bool -> IO L.ByteString)
               | IOYYY           (L.ByteString -> B.ByteString ->
                                     IO L.ByteString)
               | Handler         (B.ByteString -> ContentHandlerResult)
               | UnsafeHandler   (B.ByteString -> UnsafeContentHandlerResult)
               | AsyncHandler    (B.ByteString -> IO ContentHandlerResult)
               | AsyncHandlerRB  (L.ByteString -> B.ByteString ->
                                     IO ContentHandlerResult)

data NgxExportTypeAmbiguityTag = Unambiguous
                               | YYSync
                               | YYDefHandler
                               | IOYYSync
                               | IOYYAsync

do
    TyConI (DataD _ _ _ EXTRA_WILDCARD_BEFORE_CON tCs _) <-
        reify ''NgxExport
    TyConI (DataD _ _ _ EXTRA_WILDCARD_BEFORE_CON aCs _) <-
        reify ''NgxExportTypeAmbiguityTag
    let tName = mkName "exportType"
        aName = mkName "exportTypeAmbiguity"
        tCons = map (\(NormalC con [(_, typ)]) -> (con, typ)) tCs
        aCons = map (\(NormalC con []) -> con) aCs
    sequence $
        [sigD tName [t|NgxExport -> IO CInt|]
        ,funD tName $
             map (\(fst -> c, i) ->
                    clause [conP c [wildP]] (normalB [|return i|]) []
                 ) (zip tCons [1 ..] :: [((Name, Type), Int)])
        ,sigD aName [t|NgxExportTypeAmbiguityTag -> IO CInt|]
        ,funD aName $
             map (\(c, i) ->
                    clause [conP c []] (normalB [|return i|]) []
                 ) (zip aCons [0 ..] :: [(Name, Int)])
        ]
        ++
        map (\(c, t) -> tySynD (mkName $ nameBase c) [] $ return t) tCons

ngxExport' :: (Name -> Q Exp) ->
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport' :: (Name -> Q Exp)
-> Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport' m :: Name -> Q Exp
m e :: Name
e a :: Name
a h :: Name
h t :: Q Type
t f :: Name
f = [Q Dec] -> Q [Dec]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
    [Name -> Q Type -> Q Dec
sigD Name
nameFt Q Type
typeFt
    ,Name -> [ClauseQ] -> Q Dec
funD Name
nameFt ([ClauseQ] -> Q Dec) -> [ClauseQ] -> Q Dec
forall a b. (a -> b) -> a -> b
$ Q Exp -> [ClauseQ]
body [|exportType $cefVar|]
    ,Foreign -> Dec
ForeignD (Foreign -> Dec) -> (Type -> Foreign) -> Type -> Dec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Callconv -> String -> Name -> Type -> Foreign
ExportF Callconv
CCall String
ftName Name
nameFt (Type -> Dec) -> Q Type -> Q Dec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Q Type
typeFt
    ,Name -> Q Type -> Q Dec
sigD Name
nameFta Q Type
typeFta
    ,Name -> [ClauseQ] -> Q Dec
funD Name
nameFta ([ClauseQ] -> Q Dec) -> [ClauseQ] -> Q Dec
forall a b. (a -> b) -> a -> b
$ Q Exp -> [ClauseQ]
body [|exportTypeAmbiguity $(conE a)|]
    ,Foreign -> Dec
ForeignD (Foreign -> Dec) -> (Type -> Foreign) -> Type -> Dec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Callconv -> String -> Name -> Type -> Foreign
ExportF Callconv
CCall String
ftaName Name
nameFta (Type -> Dec) -> Q Type -> Q Dec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Q Type
typeFta
    ,Name -> Q Type -> Q Dec
sigD Name
nameF Q Type
t
    ,Name -> [ClauseQ] -> Q Dec
funD Name
nameF ([ClauseQ] -> Q Dec) -> [ClauseQ] -> Q Dec
forall a b. (a -> b) -> a -> b
$ Q Exp -> [ClauseQ]
body [|$(varE h) $efVar|]
    ,Foreign -> Dec
ForeignD (Foreign -> Dec) -> (Type -> Foreign) -> Type -> Dec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Callconv -> String -> Name -> Type -> Foreign
ExportF Callconv
CCall String
fName Name
nameF (Type -> Dec) -> Q Type -> Q Dec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Q Type
t
    ]
    where efVar :: Q Exp
efVar   = Name -> Q Exp
m Name
f
          cefVar :: Q Exp
cefVar  = Name -> Q Exp
conE Name
e Q Exp -> Q Exp -> Q Exp
`appE` Q Exp
efVar
          fName :: String
fName   = "ngx_hs_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
nameBase Name
f
          nameF :: Name
nameF   = String -> Name
mkName String
fName
          ftName :: String
ftName  = "type_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fName
          nameFt :: Name
nameFt  = String -> Name
mkName String
ftName
          typeFt :: Q Type
typeFt  = [t|IO CInt|]
          ftaName :: String
ftaName = "ambiguity_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fName
          nameFta :: Name
nameFta = String -> Name
mkName String
ftaName
          typeFta :: Q Type
typeFta = [t|IO CInt|]
          body :: Q Exp -> [ClauseQ]
body b :: Q Exp
b  = [[PatQ] -> BodyQ -> [Q Dec] -> ClauseQ
clause [] (Q Exp -> BodyQ
normalB Q Exp
b) []]

ngxExport :: Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport :: Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport = (Name -> Q Exp)
-> Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport' Name -> Q Exp
varE

ngxExportC :: Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExportC :: Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExportC = (Name -> Q Exp)
-> Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport' ((Name -> Q Exp)
 -> Name -> Name -> Name -> Q Type -> Name -> Q [Dec])
-> (Name -> Q Exp)
-> Name
-> Name
-> Name
-> Q Type
-> Name
-> Q [Dec]
forall a b. (a -> b) -> a -> b
$ Maybe (Q Exp) -> Q Exp -> Maybe (Q Exp) -> Q Exp
infixE (Q Exp -> Maybe (Q Exp)
forall a. a -> Maybe a
Just (Q Exp -> Maybe (Q Exp)) -> Q Exp -> Maybe (Q Exp)
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
varE 'const) (Name -> Q Exp
varE '(.)) (Maybe (Q Exp) -> Q Exp)
-> (Name -> Maybe (Q Exp)) -> Name -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q Exp -> Maybe (Q Exp)
forall a. a -> Maybe a
Just (Q Exp -> Maybe (Q Exp))
-> (Name -> Q Exp) -> Name -> Maybe (Q Exp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Q Exp
varE

-- | Exports a function of type
--
-- @
-- 'String' -> 'String'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportSS :: Name -> Q [Dec]
ngxExportSS :: Name -> Q [Dec]
ngxExportSS =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'SS 'Unambiguous 'sS
    [t|CString -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'String' -> 'String' -> 'String'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportSSS :: Name -> Q [Dec]
ngxExportSSS :: Name -> Q [Dec]
ngxExportSSS =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'SSS 'Unambiguous 'sSS
    [t|CString -> CInt -> CString -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- ['String'] -> 'String'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportSLS :: Name -> Q [Dec]
ngxExportSLS :: Name -> Q [Dec]
ngxExportSLS =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'SLS 'Unambiguous 'sLS
    [t|Ptr NgxStrType -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'String' -> 'Bool'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportBS :: Name -> Q [Dec]
ngxExportBS :: Name -> Q [Dec]
ngxExportBS =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'BS 'Unambiguous 'bS
    [t|CString -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'String' -> 'String' -> 'Bool'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportBSS :: Name -> Q [Dec]
ngxExportBSS :: Name -> Q [Dec]
ngxExportBSS =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'BSS 'Unambiguous 'bSS
    [t|CString -> CInt -> CString -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- ['String'] -> 'Bool'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportBLS :: Name -> Q [Dec]
ngxExportBLS :: Name -> Q [Dec]
ngxExportBLS =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'BLS 'Unambiguous 'bLS
    [t|Ptr NgxStrType -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'L.ByteString'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportYY :: Name -> Q [Dec]
ngxExportYY :: Name -> Q [Dec]
ngxExportYY =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'YY 'YYSync 'yY
    [t|CString -> CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr (StablePtr L.ByteString) -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'Bool'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportBY :: Name -> Q [Dec]
ngxExportBY :: Name -> Q [Dec]
ngxExportBY =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'BY 'Unambiguous 'bY
    [t|CString -> CInt ->
       Ptr CString -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'IO' 'L.ByteString'
-- @
--
-- for using in directive __/haskell_run/__.
ngxExportIOYY :: Name -> Q [Dec]
ngxExportIOYY :: Name -> Q [Dec]
ngxExportIOYY =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExportC 'IOYY 'IOYYSync 'ioyY
    [t|CString -> CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr (StablePtr L.ByteString) -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'IO' 'L.ByteString'
-- @
--
-- for using in directive __/haskell_run_async/__.
ngxExportAsyncIOYY :: Name -> Q [Dec]
ngxExportAsyncIOYY :: Name -> Q [Dec]
ngxExportAsyncIOYY =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExportC 'IOYY 'IOYYAsync 'asyncIOYY
    [t|CString -> CInt -> CInt -> CInt -> Ptr CUInt -> CUInt -> CUInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))|]

-- | Exports a function of type
--
-- @
-- 'L.ByteString' -> 'B.ByteString' -> 'IO' 'L.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.
ngxExportAsyncOnReqBody :: Name -> Q [Dec]
ngxExportAsyncOnReqBody :: Name -> Q [Dec]
ngxExportAsyncOnReqBody =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'IOYYY 'Unambiguous 'asyncIOYYY
    [t|Ptr NgxStrType -> Ptr NgxStrType -> CInt ->
       CString -> CInt -> CInt -> CUInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'Bool' -> 'IO' 'L.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.
ngxExportServiceIOYY :: Name -> Q [Dec]
ngxExportServiceIOYY :: Name -> Q [Dec]
ngxExportServiceIOYY =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'IOYY 'IOYYAsync 'asyncIOYY
    [t|CString -> CInt -> CInt -> CInt -> Ptr CUInt -> CUInt -> CUInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'ContentHandlerResult'
-- @
--
-- for using in directives __/haskell_content/__ and
-- __/haskell_static_content/__.
ngxExportHandler :: Name -> Q [Dec]
ngxExportHandler :: Name -> Q [Dec]
ngxExportHandler =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'Handler 'Unambiguous 'handler
    [t|CString -> CInt -> Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr CString -> Ptr CSize -> Ptr (StablePtr B.ByteString) -> Ptr CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) ->
       Ptr (StablePtr L.ByteString) -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'L.ByteString'
-- @
--
-- for using in directives __/haskell_content/__ and
-- __/haskell_static_content/__.
ngxExportDefHandler :: Name -> Q [Dec]
ngxExportDefHandler :: Name -> Q [Dec]
ngxExportDefHandler =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'YY 'YYDefHandler 'defHandler
    [t|CString -> CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr CString ->
       Ptr (StablePtr L.ByteString) -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'UnsafeContentHandlerResult'
-- @
--
-- for using in directive __/haskell_unsafe_content/__.
ngxExportUnsafeHandler :: Name -> Q [Dec]
ngxExportUnsafeHandler :: Name -> Q [Dec]
ngxExportUnsafeHandler =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'UnsafeHandler 'Unambiguous 'unsafeHandler
    [t|CString -> CInt -> Ptr CString -> Ptr CSize ->
       Ptr CString -> Ptr CSize -> Ptr CInt -> IO CUInt|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'IO' 'ContentHandlerResult'
-- @
--
-- for using in directive __/haskell_async_content/__.
ngxExportAsyncHandler :: Name -> Q [Dec]
ngxExportAsyncHandler :: Name -> Q [Dec]
ngxExportAsyncHandler =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'AsyncHandler 'Unambiguous 'asyncHandler
    [t|CString -> CInt -> CInt -> CUInt ->
       Ptr CString -> Ptr CSize -> Ptr (StablePtr B.ByteString) -> Ptr CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))|]

-- | Exports a function of type
--
-- @
-- 'L.ByteString' -> 'B.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.
ngxExportAsyncHandlerOnReqBody :: Name -> Q [Dec]
ngxExportAsyncHandlerOnReqBody :: Name -> Q [Dec]
ngxExportAsyncHandlerOnReqBody =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExport 'AsyncHandlerRB 'Unambiguous 'asyncHandlerRB
    [t|Ptr NgxStrType -> Ptr NgxStrType -> CInt ->
       CString -> CInt -> CInt -> CUInt ->
       Ptr CString -> Ptr CSize -> Ptr (StablePtr B.ByteString) -> Ptr CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))|]

-- | Exports a function of type
--
-- @
-- 'B.ByteString' -> 'IO' 'L.ByteString'
-- @
--
-- for using in directives __/haskell_service_hook/__ and
-- __/haskell_service_update_hook/__.
ngxExportServiceHook :: Name -> Q [Dec]
ngxExportServiceHook :: Name -> Q [Dec]
ngxExportServiceHook =
    Name -> Name -> Name -> Q Type -> Name -> Q [Dec]
ngxExportC 'IOYY 'IOYYSync 'ioyYWithFree
    [t|CString -> CInt ->
       Ptr (Ptr NgxStrType) -> Ptr CInt ->
       Ptr (StablePtr L.ByteString) -> IO CUInt|]

data NgxStrType = NgxStrType CSize CString

instance Storable NgxStrType where
    alignment :: NgxStrType -> Int
alignment = Int -> NgxStrType -> Int
forall a b. a -> b -> a
const (Int -> NgxStrType -> Int) -> Int -> NgxStrType -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (CSize -> Int
forall a. Storable a => a -> Int
alignment (CSize
forall a. HasCallStack => a
undefined :: CSize))
                            (CString -> Int
forall a. Storable a => a -> Int
alignment (CString
forall a. HasCallStack => a
undefined :: CString))
    sizeOf :: NgxStrType -> Int
sizeOf = (2 Int -> Int -> Int
forall a. Num a => a -> a -> a
*) (Int -> Int) -> (NgxStrType -> Int) -> NgxStrType -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NgxStrType -> Int
forall a. Storable a => a -> Int
alignment  -- must always be correct for
                                -- aligned struct ngx_str_t
    peek :: Ptr NgxStrType -> IO NgxStrType
peek p :: Ptr NgxStrType
p = do
        CSize
n <- Ptr NgxStrType -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr NgxStrType
p 0
        CString
s <- Ptr NgxStrType -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr NgxStrType
p (Int -> IO CString) -> Int -> IO CString
forall a b. (a -> b) -> a -> b
$ NgxStrType -> Int
forall a. Storable a => a -> Int
alignment (NgxStrType
forall a. HasCallStack => a
undefined :: NgxStrType)
        NgxStrType -> IO NgxStrType
forall (m :: * -> *) a. Monad m => a -> m a
return (NgxStrType -> IO NgxStrType) -> NgxStrType -> IO NgxStrType
forall a b. (a -> b) -> a -> b
$ CSize -> CString -> NgxStrType
NgxStrType CSize
n CString
s
    poke :: Ptr NgxStrType -> NgxStrType -> IO ()
poke p :: Ptr NgxStrType
p x :: NgxStrType
x@(NgxStrType n :: CSize
n s :: CString
s) = do
        Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr NgxStrType -> Ptr CSize
forall a b. Ptr a -> Ptr b
castPtr Ptr NgxStrType
p) CSize
n
        Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr NgxStrType -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr NgxStrType
p (Int -> Ptr CString) -> Int -> Ptr CString
forall a b. (a -> b) -> a -> b
$ NgxStrType -> Int
forall a. Storable a => a -> Int
alignment NgxStrType
x) CString
s

data ServiceHookInterrupt = ServiceHookInterrupt

instance Exception ServiceHookInterrupt
instance Show ServiceHookInterrupt where
    show :: ServiceHookInterrupt -> String
show = String -> ServiceHookInterrupt -> String
forall a b. a -> b -> a
const "Service was interrupted by a service hook"

-- | 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
newtype TerminateWorkerProcess =
    TerminateWorkerProcess String  -- ^ Contains the message to log
    deriving TerminateWorkerProcess -> TerminateWorkerProcess -> Bool
(TerminateWorkerProcess -> TerminateWorkerProcess -> Bool)
-> (TerminateWorkerProcess -> TerminateWorkerProcess -> Bool)
-> Eq TerminateWorkerProcess
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminateWorkerProcess -> TerminateWorkerProcess -> Bool
$c/= :: TerminateWorkerProcess -> TerminateWorkerProcess -> Bool
== :: TerminateWorkerProcess -> TerminateWorkerProcess -> Bool
$c== :: TerminateWorkerProcess -> TerminateWorkerProcess -> Bool
Eq

instance Exception TerminateWorkerProcess
instance Show TerminateWorkerProcess where
    show :: TerminateWorkerProcess -> String
show (TerminateWorkerProcess s :: String
s) = String
s

-- | 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
newtype RestartWorkerProcess =
    RestartWorkerProcess String  -- ^ Contains the message to log
    deriving RestartWorkerProcess -> RestartWorkerProcess -> Bool
(RestartWorkerProcess -> RestartWorkerProcess -> Bool)
-> (RestartWorkerProcess -> RestartWorkerProcess -> Bool)
-> Eq RestartWorkerProcess
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestartWorkerProcess -> RestartWorkerProcess -> Bool
$c/= :: RestartWorkerProcess -> RestartWorkerProcess -> Bool
== :: RestartWorkerProcess -> RestartWorkerProcess -> Bool
$c== :: RestartWorkerProcess -> RestartWorkerProcess -> Bool
Eq

instance Exception RestartWorkerProcess
instance Show RestartWorkerProcess where
    show :: RestartWorkerProcess -> String
show (RestartWorkerProcess s :: String
s) = String
s

-- | 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
data WorkerProcessIsExiting = WorkerProcessIsExiting deriving (Int -> WorkerProcessIsExiting -> String -> String
[WorkerProcessIsExiting] -> String -> String
WorkerProcessIsExiting -> String
(Int -> WorkerProcessIsExiting -> String -> String)
-> (WorkerProcessIsExiting -> String)
-> ([WorkerProcessIsExiting] -> String -> String)
-> Show WorkerProcessIsExiting
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [WorkerProcessIsExiting] -> String -> String
$cshowList :: [WorkerProcessIsExiting] -> String -> String
show :: WorkerProcessIsExiting -> String
$cshow :: WorkerProcessIsExiting -> String
showsPrec :: Int -> WorkerProcessIsExiting -> String -> String
$cshowsPrec :: Int -> WorkerProcessIsExiting -> String -> String
Show, WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool
(WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool)
-> (WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool)
-> Eq WorkerProcessIsExiting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool
$c/= :: WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool
== :: WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool
$c== :: WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool
Eq)

instance Exception WorkerProcessIsExiting where
  fromException :: SomeException -> Maybe WorkerProcessIsExiting
fromException = SomeException -> Maybe WorkerProcessIsExiting
forall e. Exception e => SomeException -> Maybe e
asyncExceptionFromException
  toException :: WorkerProcessIsExiting -> SomeException
toException = WorkerProcessIsExiting -> SomeException
forall e. Exception e => e -> SomeException
asyncExceptionToException

-- | 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
data FinalizeHTTPRequest =
    FinalizeHTTPRequest Int (Maybe String)  -- ^ Contains HTTP status and body
    deriving FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool
(FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool)
-> (FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool)
-> Eq FinalizeHTTPRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool
$c/= :: FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool
== :: FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool
$c== :: FinalizeHTTPRequest -> FinalizeHTTPRequest -> Bool
Eq

instance Exception FinalizeHTTPRequest
instance Show FinalizeHTTPRequest where
    show :: FinalizeHTTPRequest -> String
show (FinalizeHTTPRequest _ (Just s :: String
s)) = String
s
    show (FinalizeHTTPRequest _ Nothing) = ""

safeMallocBytes :: Int -> IO (Ptr a)
safeMallocBytes :: Int -> IO (Ptr a)
safeMallocBytes =
    (IO (Ptr a) -> (IOError -> IO (Ptr a)) -> IO (Ptr a))
-> (IOError -> IO (Ptr a)) -> IO (Ptr a) -> IO (Ptr a)
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Ptr a) -> (IOError -> IO (Ptr a)) -> IO (Ptr a)
forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError (IO (Ptr a) -> IOError -> IO (Ptr a)
forall a b. a -> b -> a
const (IO (Ptr a) -> IOError -> IO (Ptr a))
-> IO (Ptr a) -> IOError -> IO (Ptr a)
forall a b. (a -> b) -> a -> b
$ Ptr a -> IO (Ptr a)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr a
forall a. Ptr a
nullPtr) (IO (Ptr a) -> IO (Ptr a))
-> (Int -> IO (Ptr a)) -> Int -> IO (Ptr a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IO (Ptr a)
forall a. Int -> IO (Ptr a)
mallocBytes
{-# INLINE safeMallocBytes #-}

safeNewCStringLen :: String -> IO CStringLen
safeNewCStringLen :: String -> IO CStringLen
safeNewCStringLen =
    (IO CStringLen -> (IOError -> IO CStringLen) -> IO CStringLen)
-> (IOError -> IO CStringLen) -> IO CStringLen -> IO CStringLen
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO CStringLen -> (IOError -> IO CStringLen) -> IO CStringLen
forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError (IO CStringLen -> IOError -> IO CStringLen
forall a b. a -> b -> a
const (IO CStringLen -> IOError -> IO CStringLen)
-> IO CStringLen -> IOError -> IO CStringLen
forall a b. (a -> b) -> a -> b
$ CStringLen -> IO CStringLen
forall (m :: * -> *) a. Monad m => a -> m a
return (CString
forall a. Ptr a
nullPtr, -1)) (IO CStringLen -> IO CStringLen)
-> (String -> IO CStringLen) -> String -> IO CStringLen
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO CStringLen
newCStringLen
{-# INLINE safeNewCStringLen #-}

peekNgxStringArrayLen :: (CStringLen -> IO a) -> Ptr NgxStrType -> Int -> IO [a]
peekNgxStringArrayLen :: (CStringLen -> IO a) -> Ptr NgxStrType -> Int -> IO [a]
peekNgxStringArrayLen f :: CStringLen -> IO a
f x :: Ptr NgxStrType
x = [IO a] -> IO [a]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([IO a] -> IO [a]) -> (Int -> [IO a]) -> Int -> IO [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (Int -> [IO a] -> [IO a]) -> [IO a] -> [Int] -> [IO a]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\k :: Int
k ->
            ((Ptr NgxStrType -> Int -> IO NgxStrType
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr NgxStrType
x Int
k IO NgxStrType -> (NgxStrType -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\(NgxStrType (I m :: Int
m) y :: CString
y) -> CStringLen -> IO a
f (CString
y, Int
m))) IO a -> [IO a] -> [IO a]
forall a. a -> [a] -> [a]
:)
          ) [] ([Int] -> [IO a]) -> (Int -> [Int]) -> Int -> [IO a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> [Int] -> [Int]) -> [Int] -> Int -> [Int]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take [0 ..]
{-# SPECIALIZE INLINE peekNgxStringArrayLen ::
    (CStringLen -> IO String) -> Ptr NgxStrType -> Int ->
        IO [String] #-}
{-# SPECIALIZE INLINE peekNgxStringArrayLen ::
    (CStringLen -> IO B.ByteString) -> Ptr NgxStrType -> Int ->
        IO [B.ByteString] #-}

peekNgxStringArrayLenLS :: Ptr NgxStrType -> Int -> IO [String]
peekNgxStringArrayLenLS :: Ptr NgxStrType -> Int -> IO [String]
peekNgxStringArrayLenLS =
    (CStringLen -> IO String) -> Ptr NgxStrType -> Int -> IO [String]
forall a. (CStringLen -> IO a) -> Ptr NgxStrType -> Int -> IO [a]
peekNgxStringArrayLen CStringLen -> IO String
peekCStringLen

peekNgxStringArrayLenY :: Ptr NgxStrType -> Int -> IO L.ByteString
peekNgxStringArrayLenY :: Ptr NgxStrType -> Int -> IO ByteString
peekNgxStringArrayLenY =
    (([ByteString] -> ByteString) -> IO [ByteString] -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [ByteString] -> ByteString
L.fromChunks (IO [ByteString] -> IO ByteString)
-> (Int -> IO [ByteString]) -> Int -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Int -> IO [ByteString]) -> Int -> IO ByteString)
-> (Ptr NgxStrType -> Int -> IO [ByteString])
-> Ptr NgxStrType
-> Int
-> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CStringLen -> IO ByteString)
-> Ptr NgxStrType -> Int -> IO [ByteString]
forall a. (CStringLen -> IO a) -> Ptr NgxStrType -> Int -> IO [a]
peekNgxStringArrayLen CStringLen -> IO ByteString
B.unsafePackCStringLen

pokeCStringLen :: Storable a => CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen :: CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen x :: CString
x n :: a
n p :: Ptr CString
p s :: Ptr a
s = Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CString
p CString
x IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr a -> a -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr a
s a
n
{-# SPECIALIZE INLINE pokeCStringLen ::
    CString -> CInt -> Ptr CString -> Ptr CInt -> IO () #-}
{-# SPECIALIZE INLINE pokeCStringLen ::
    CString -> CSize -> Ptr CString -> Ptr CSize -> IO () #-}

toBuffers :: L.ByteString -> Ptr NgxStrType -> IO (Ptr NgxStrType, Int)
toBuffers :: ByteString -> Ptr NgxStrType -> IO (Ptr NgxStrType, Int)
toBuffers (ByteString -> Bool
L.null -> Bool
True) _ =
    (Ptr NgxStrType, Int) -> IO (Ptr NgxStrType, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr NgxStrType
forall a. Ptr a
nullPtr, 0)
toBuffers s :: ByteString
s p :: Ptr NgxStrType
p = do
    let n :: Int
n = (Int -> ByteString -> Int) -> Int -> ByteString -> Int
forall a. (a -> ByteString -> a) -> a -> ByteString -> a
L.foldlChunks (Int -> ByteString -> Int
forall a b. a -> b -> a
const (Int -> ByteString -> Int)
-> (Int -> Int) -> Int -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Enum a => a -> a
succ) 0 ByteString
s
    if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 1 Bool -> Bool -> Bool
&& Ptr NgxStrType
p Ptr NgxStrType -> Ptr NgxStrType -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr NgxStrType
forall a. Ptr a
nullPtr
        then do
            ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ([ByteString] -> ByteString
forall a. [a] -> a
head ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
L.toChunks ByteString
s) ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
                \(x :: CString
x, I l :: CSize
l) -> Ptr NgxStrType -> NgxStrType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr NgxStrType
p (NgxStrType -> IO ()) -> NgxStrType -> IO ()
forall a b. (a -> b) -> a -> b
$ CSize -> CString -> NgxStrType
NgxStrType CSize
l CString
x
            (Ptr NgxStrType, Int) -> IO (Ptr NgxStrType, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr NgxStrType
p, 1)
        else do
            Ptr NgxStrType
t <- Int -> IO (Ptr NgxStrType)
forall a. Int -> IO (Ptr a)
safeMallocBytes (Int -> IO (Ptr NgxStrType)) -> Int -> IO (Ptr NgxStrType)
forall a b. (a -> b) -> a -> b
$ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* NgxStrType -> Int
forall a. Storable a => a -> Int
sizeOf (NgxStrType
forall a. HasCallStack => a
undefined :: NgxStrType)
            if Ptr NgxStrType
t Ptr NgxStrType -> Ptr NgxStrType -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr NgxStrType
forall a. Ptr a
nullPtr
                then (Ptr NgxStrType, Int) -> IO (Ptr NgxStrType, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr NgxStrType
forall a. Ptr a
nullPtr, -1)
                else (Ptr NgxStrType
t, ) (Int -> (Ptr NgxStrType, Int))
-> IO Int -> IO (Ptr NgxStrType, Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                        (IO Int -> ByteString -> IO Int) -> IO Int -> ByteString -> IO Int
forall a. (a -> ByteString -> a) -> a -> ByteString -> a
L.foldlChunks
                            (\a :: IO Int
a c :: ByteString
c -> do
                                Int
off <- IO Int
a
                                ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
c ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
                                    \(x :: CString
x, I l :: CSize
l) ->
                                        Ptr NgxStrType -> Int -> NgxStrType -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr NgxStrType
t Int
off (NgxStrType -> IO ()) -> NgxStrType -> IO ()
forall a b. (a -> b) -> a -> b
$ CSize -> CString -> NgxStrType
NgxStrType CSize
l CString
x
                                Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1
                            ) (Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return 0) ByteString
s

pokeLazyByteString :: L.ByteString ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr (StablePtr L.ByteString) -> IO ()
pokeLazyByteString :: ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString s :: ByteString
s p :: Ptr (Ptr NgxStrType)
p pl :: Ptr CInt
pl spd :: Ptr (StablePtr ByteString)
spd = do
    Ptr NgxStrType
pv <- Ptr (Ptr NgxStrType) -> IO (Ptr NgxStrType)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr NgxStrType)
p
    PtrLen t :: Ptr NgxStrType
t l :: CInt
l <- ByteString -> Ptr NgxStrType -> IO (Ptr NgxStrType, Int)
toBuffers ByteString
s Ptr NgxStrType
pv
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
l CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 1 Bool -> Bool -> Bool
|| Ptr NgxStrType
pv Ptr NgxStrType -> Ptr NgxStrType -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr NgxStrType
forall a. Ptr a
nullPtr) (Ptr (Ptr NgxStrType) -> Ptr NgxStrType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (Ptr NgxStrType)
p Ptr NgxStrType
t) IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CInt
pl CInt
l
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Ptr NgxStrType
t Ptr NgxStrType -> Ptr NgxStrType -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr NgxStrType
forall a. Ptr a
nullPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> IO (StablePtr ByteString)
forall a. a -> IO (StablePtr a)
newStablePtr ByteString
s IO (StablePtr ByteString)
-> (StablePtr ByteString -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr (StablePtr ByteString) -> StablePtr ByteString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (StablePtr ByteString)
spd

pokeContentTypeAndStatus :: B.ByteString ->
    Ptr CString -> Ptr CSize -> Ptr CInt -> CInt -> IO CSize
pokeContentTypeAndStatus :: ByteString
-> Ptr CString -> Ptr CSize -> Ptr CInt -> CInt -> IO CSize
pokeContentTypeAndStatus ct :: ByteString
ct pct :: Ptr CString
pct plct :: Ptr CSize
plct pst :: Ptr CInt
pst st :: CInt
st = do
    PtrLen sct :: CString
sct lct :: CSize
lct <- ByteString -> (CStringLen -> IO CStringLen) -> IO CStringLen
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
ct CStringLen -> IO CStringLen
forall (m :: * -> *) a. Monad m => a -> m a
return
    CString -> CSize -> Ptr CString -> Ptr CSize -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
sct CSize
lct Ptr CString
pct Ptr CSize
plct IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CInt
pst CInt
st
    CSize -> IO CSize
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
lct

peekRequestBodyChunks :: Ptr NgxStrType -> Ptr NgxStrType -> Int ->
    IO L.ByteString
peekRequestBodyChunks :: Ptr NgxStrType -> Ptr NgxStrType -> Int -> IO ByteString
peekRequestBodyChunks tmpf :: Ptr NgxStrType
tmpf b :: Ptr NgxStrType
b m :: Int
m =
    if Ptr NgxStrType
tmpf Ptr NgxStrType -> Ptr NgxStrType -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr NgxStrType
forall a. Ptr a
nullPtr
        then do
            ByteString
c <- Ptr NgxStrType -> IO NgxStrType
forall a. Storable a => Ptr a -> IO a
peek Ptr NgxStrType
tmpf IO NgxStrType -> (NgxStrType -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                (\(NgxStrType (I l :: Int
l) s :: CString
s) -> CStringLen -> IO String
peekCStringLen (CString
s, Int
l)) IO String -> (String -> IO ByteString) -> IO ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                    String -> IO ByteString
L.readFile
            ByteString -> Int64
L.length ByteString
c Int64 -> IO ByteString -> IO ByteString
forall a b. a -> b -> b
`seq` ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
c
        else Ptr NgxStrType -> Int -> IO ByteString
peekNgxStringArrayLenY Ptr NgxStrType
b Int
m

pokeAsyncHandlerData :: B.ByteString -> Ptr CString -> Ptr CSize ->
    Ptr (StablePtr B.ByteString) -> Ptr CInt -> CInt -> HTTPHeaders ->
    Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) -> IO ()
pokeAsyncHandlerData :: ByteString
-> Ptr CString
-> Ptr CSize
-> Ptr (StablePtr ByteString)
-> Ptr CInt
-> CInt
-> HTTPHeaders
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeAsyncHandlerData ct :: ByteString
ct pct :: Ptr CString
pct plct :: Ptr CSize
plct spct :: Ptr (StablePtr ByteString)
spct pst :: Ptr CInt
pst st :: CInt
st rhs :: HTTPHeaders
rhs prhs :: Ptr (Ptr NgxStrType)
prhs plrhs :: Ptr CInt
plrhs sprhs :: Ptr (StablePtr ByteString)
sprhs = do
    CSize
lct <- ByteString
-> Ptr CString -> Ptr CSize -> Ptr CInt -> CInt -> IO CSize
pokeContentTypeAndStatus ByteString
ct Ptr CString
pct Ptr CSize
plct Ptr CInt
pst CInt
st
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CSize
lct CSize -> CSize -> Bool
forall a. Ord a => a -> a -> Bool
> 0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> IO (StablePtr ByteString)
forall a. a -> IO (StablePtr a)
newStablePtr ByteString
ct IO (StablePtr ByteString)
-> (StablePtr ByteString -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr (StablePtr ByteString) -> StablePtr ByteString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (StablePtr ByteString)
spct
    ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString (HTTPHeaders -> ByteString
fromHTTPHeaders HTTPHeaders
rhs) Ptr (Ptr NgxStrType)
prhs Ptr CInt
plrhs Ptr (StablePtr ByteString)
sprhs

safeHandler :: Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler :: Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler p :: Ptr CString
p pl :: Ptr CInt
pl = (SomeException -> IO CUInt) -> IO CUInt -> IO CUInt
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle ((SomeException -> IO CUInt) -> IO CUInt -> IO CUInt)
-> (SomeException -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \e :: SomeException
e -> do
    PtrLen x :: CString
x l :: CInt
l <- String -> IO CStringLen
safeNewCStringLen (String -> IO CStringLen) -> String -> IO CStringLen
forall a b. (a -> b) -> a -> b
$ SomeException -> String
forall a. Show a => a -> String
show (SomeException
e :: SomeException)
    CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
x CInt
l Ptr CString
p Ptr CInt
pl
    CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 1

safeYYHandler :: IO (L.ByteString, CUInt) -> IO (L.ByteString, CUInt)
safeYYHandler :: IO (ByteString, CUInt) -> IO (ByteString, CUInt)
safeYYHandler = (SomeException -> IO (ByteString, CUInt))
-> IO (ByteString, CUInt) -> IO (ByteString, CUInt)
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle ((SomeException -> IO (ByteString, CUInt))
 -> IO (ByteString, CUInt) -> IO (ByteString, CUInt))
-> (SomeException -> IO (ByteString, CUInt))
-> IO (ByteString, CUInt)
-> IO (ByteString, CUInt)
forall a b. (a -> b) -> a -> b
$ \e :: SomeException
e ->
    (ByteString, CUInt) -> IO (ByteString, CUInt)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ByteString
C8L.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ SomeException -> String
forall a. Show a => a -> String
show (SomeException
e :: SomeException), 1)
{-# INLINE safeYYHandler #-}

safeAsyncYYHandler :: IO (L.ByteString, (CUInt, Bool)) ->
    IO (L.ByteString, (CUInt, Bool))
safeAsyncYYHandler :: IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
safeAsyncYYHandler = (SomeException -> IO (ByteString, (CUInt, Bool)))
-> IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle ((SomeException -> IO (ByteString, (CUInt, Bool)))
 -> IO (ByteString, (CUInt, Bool))
 -> IO (ByteString, (CUInt, Bool)))
-> (SomeException -> IO (ByteString, (CUInt, Bool)))
-> IO (ByteString, (CUInt, Bool))
-> IO (ByteString, (CUInt, Bool))
forall a b. (a -> b) -> a -> b
$ \e :: SomeException
e ->
    (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ByteString
C8L.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ SomeException -> String
forall a. Show a => a -> String
show SomeException
e,
            (case SomeException -> Maybe ServiceHookInterrupt
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
                Just ServiceHookInterrupt -> 2
                _ -> case SomeException -> Maybe TerminateWorkerProcess
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
                    Just (TerminateWorkerProcess _) -> 3
                    _ -> case SomeException -> Maybe RestartWorkerProcess
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
                        Just (RestartWorkerProcess _) -> 4
                        _ -> case SomeException -> Maybe FinalizeHTTPRequest
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
                            Just (FinalizeHTTPRequest st :: Int
st (Just _)) ->
                                0x80000000 CUInt -> CUInt -> CUInt
forall a. Bits a => a -> a -> a
.|. Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
st
                            Just (FinalizeHTTPRequest st :: Int
st Nothing) ->
                                0xC0000000 CUInt -> CUInt -> CUInt
forall a. Bits a => a -> a -> a
.|. Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
st
                            _ -> 1
            ,case SomeException -> Maybe WorkerProcessIsExiting
forall e. Exception e => SomeException -> Maybe e
asyncExceptionFromException SomeException
e of
                Just WorkerProcessIsExiting -> Bool
True
                _ -> Bool
False
            )
           )
{-# INLINE safeAsyncYYHandler #-}

fromHTTPHeaders :: HTTPHeaders -> L.ByteString
fromHTTPHeaders :: HTTPHeaders -> ByteString
fromHTTPHeaders = [ByteString] -> ByteString
L.fromChunks ([ByteString] -> ByteString)
-> (HTTPHeaders -> [ByteString]) -> HTTPHeaders -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ByteString, ByteString) -> [ByteString] -> [ByteString])
-> [ByteString] -> HTTPHeaders -> [ByteString]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(ByteString -> ByteString
z -> ByteString
a, ByteString -> ByteString
z -> ByteString
b) -> ([ByteString
a, ByteString
b] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++)) []
    where z :: ByteString -> ByteString
z s :: ByteString
s | ByteString -> Bool
B.null ByteString
s = Word8 -> ByteString
B.singleton 0
              | Bool
otherwise = ByteString
s

isEINTR :: IOError -> Bool
isEINTR :: IOError -> Bool
isEINTR = (CInt -> Maybe CInt
forall a. a -> Maybe a
Just ((\(Errno i :: CInt
i) -> CInt
i) Errno
eINTR) Maybe CInt -> Maybe CInt -> Bool
forall a. Eq a => a -> a -> Bool
==) (Maybe CInt -> Bool) -> (IOError -> Maybe CInt) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Maybe CInt
ioe_errno
{-# INLINE isEINTR #-}

sS :: SS -> CString -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
sS :: (String -> String)
-> CString -> CInt -> Ptr CString -> Ptr CInt -> IO CUInt
sS f :: String -> String
f x :: CString
x (I n :: Int
n) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        PtrLen s :: CString
s l :: CInt
l <- String -> String
f (String -> String) -> IO String -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO String
peekCStringLen (CString
x, Int
n)
                        IO String -> (String -> IO CStringLen) -> IO CStringLen
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO CStringLen
newCStringLen
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
s CInt
l Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 0

sSS :: SSS -> CString -> CInt -> CString -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
sSS :: (String -> String -> String)
-> CString
-> CInt
-> CString
-> CInt
-> Ptr CString
-> Ptr CInt
-> IO CUInt
sSS f :: String -> String -> String
f x :: CString
x (I n :: Int
n) y :: CString
y (I m :: Int
m) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        PtrLen s :: CString
s l :: CInt
l <- String -> String -> String
f (String -> String -> String) -> IO String -> IO (String -> String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO String
peekCStringLen (CString
x, Int
n)
                        IO (String -> String) -> IO String -> IO String
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CStringLen -> IO String
peekCStringLen (CString
y, Int
m)
                        IO String -> (String -> IO CStringLen) -> IO CStringLen
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO CStringLen
newCStringLen
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
s CInt
l Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 0

sLS :: SLS -> Ptr NgxStrType -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
sLS :: SLS
-> Ptr NgxStrType -> CInt -> Ptr CString -> Ptr CInt -> IO CUInt
sLS f :: SLS
f x :: Ptr NgxStrType
x (I n :: Int
n) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        PtrLen s :: CString
s l :: CInt
l <- SLS
f SLS -> IO [String] -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr NgxStrType -> Int -> IO [String]
peekNgxStringArrayLenLS Ptr NgxStrType
x Int
n
                        IO String -> (String -> IO CStringLen) -> IO CStringLen
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO CStringLen
newCStringLen
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
s CInt
l Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 0

yY :: YY -> CString -> CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr (StablePtr L.ByteString) -> IO CUInt
yY :: YY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO CUInt
yY f :: YY
f x :: CString
x (I n :: Int
n) p :: Ptr (Ptr NgxStrType)
p pl :: Ptr CInt
pl spd :: Ptr (StablePtr ByteString)
spd = do
    (s :: ByteString
s, r :: CUInt
r) <- IO (ByteString, CUInt) -> IO (ByteString, CUInt)
safeYYHandler (IO (ByteString, CUInt) -> IO (ByteString, CUInt))
-> IO (ByteString, CUInt) -> IO (ByteString, CUInt)
forall a b. (a -> b) -> a -> b
$ do
        ByteString
s <- YY
f YY -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        (ByteString -> (ByteString, CUInt))
-> IO ByteString -> IO (ByteString, CUInt)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (, 0) (IO ByteString -> IO (ByteString, CUInt))
-> IO ByteString -> IO (ByteString, CUInt)
forall a b. (a -> b) -> a -> b
$ ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. NFData a => (a -> b) -> a -> b
$!! ByteString
s
    ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString ByteString
s Ptr (Ptr NgxStrType)
p Ptr CInt
pl Ptr (StablePtr ByteString)
spd
    CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
r

ioyYCommon :: (CStringLen -> IO B.ByteString) ->
    IOYY -> CString -> CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr (StablePtr L.ByteString) -> IO CUInt
ioyYCommon :: (CStringLen -> IO ByteString)
-> IOYY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO CUInt
ioyYCommon pack :: CStringLen -> IO ByteString
pack f :: IOYY
f x :: CString
x (I n :: Int
n) p :: Ptr (Ptr NgxStrType)
p pl :: Ptr CInt
pl spd :: Ptr (StablePtr ByteString)
spd = do
    (s :: ByteString
s, r :: CUInt
r) <- IO (ByteString, CUInt) -> IO (ByteString, CUInt)
safeYYHandler (IO (ByteString, CUInt) -> IO (ByteString, CUInt))
-> IO (ByteString, CUInt) -> IO (ByteString, CUInt)
forall a b. (a -> b) -> a -> b
$ do
        ByteString
s <- CStringLen -> IO ByteString
pack (CString
x, Int
n) IO ByteString -> (ByteString -> IO ByteString) -> IO ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IOYY -> Bool -> ByteString -> IO ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip IOYY
f Bool
False
        (ByteString -> (ByteString, CUInt))
-> IO ByteString -> IO (ByteString, CUInt)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (, 0) (IO ByteString -> IO (ByteString, CUInt))
-> IO ByteString -> IO (ByteString, CUInt)
forall a b. (a -> b) -> a -> b
$ ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. NFData a => (a -> b) -> a -> b
$!! ByteString
s
    ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString ByteString
s Ptr (Ptr NgxStrType)
p Ptr CInt
pl Ptr (StablePtr ByteString)
spd
    CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
r

ioyY :: IOYY -> CString -> CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr (StablePtr L.ByteString) -> IO CUInt
ioyY :: IOYY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO CUInt
ioyY = (CStringLen -> IO ByteString)
-> IOYY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO CUInt
ioyYCommon CStringLen -> IO ByteString
B.unsafePackCStringLen

ioyYWithFree :: IOYY -> CString -> CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr (StablePtr L.ByteString) -> IO CUInt
ioyYWithFree :: IOYY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO CUInt
ioyYWithFree = (CStringLen -> IO ByteString)
-> IOYY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO CUInt
ioyYCommon CStringLen -> IO ByteString
B.unsafePackMallocCStringLen

asyncIOFlag1b :: B.ByteString
asyncIOFlag1b :: ByteString
asyncIOFlag1b = ByteString -> ByteString
L.toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Put -> ByteString
runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ Word8 -> Put
putWord8 1

asyncIOFlag8b :: B.ByteString
asyncIOFlag8b :: ByteString
asyncIOFlag8b = ByteString -> ByteString
L.toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Put -> ByteString
runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ Word64 -> Put
putWord64host 1

asyncIOCommon :: IO (L.ByteString, Bool) ->
    CInt -> Bool -> Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))
asyncIOCommon :: IO (ByteString, Bool)
-> CInt
-> Bool
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOCommon a :: IO (ByteString, Bool)
a (I fd :: Fd
fd) efd :: Bool
efd p :: Ptr (Ptr NgxStrType)
p pl :: Ptr CInt
pl pr :: Ptr CUInt
pr spd :: Ptr (StablePtr ByteString)
spd = ((forall a. IO a -> IO a) -> IO (StablePtr (Async ())))
-> IO (StablePtr (Async ()))
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO (StablePtr (Async ())))
 -> IO (StablePtr (Async ())))
-> ((forall a. IO a -> IO a) -> IO (StablePtr (Async ())))
-> IO (StablePtr (Async ()))
forall a b. (a -> b) -> a -> b
$ \restore :: forall a. IO a -> IO a
restore ->
    IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async
    (do
        (s :: ByteString
s, (r :: CUInt
r, exiting :: Bool
exiting)) <- IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
safeAsyncYYHandler (IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool)))
-> IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
forall a b. (a -> b) -> a -> b
$
            IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
forall a. IO a -> IO a
restore (IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool)))
-> IO (ByteString, (CUInt, Bool)) -> IO (ByteString, (CUInt, Bool))
forall a b. (a -> b) -> a -> b
$ do
                (s :: ByteString
s, exiting :: Bool
exiting) <- IO (ByteString, Bool)
a
                (ByteString -> (ByteString, (CUInt, Bool)))
-> IO ByteString -> IO (ByteString, (CUInt, Bool))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (, (0, Bool
exiting)) (IO ByteString -> IO (ByteString, (CUInt, Bool)))
-> IO ByteString -> IO (ByteString, (CUInt, Bool))
forall a b. (a -> b) -> a -> b
$ ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. NFData a => (a -> b) -> a -> b
$!! ByteString
s
        ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString ByteString
s Ptr (Ptr NgxStrType)
p Ptr CInt
pl Ptr (StablePtr ByteString)
spd
        Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CUInt
pr CUInt
r
        if Bool
exiting
            then Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
efd IO ()
closeChannel
            else IO () -> IO ()
forall a. IO a -> IO a
uninterruptibleMask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                    if Bool
efd
                        then IO ()
writeFlag8b
                        else IO ()
writeFlag1b IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
closeChannel
    ) IO (Async ())
-> (Async () -> IO (StablePtr (Async ())))
-> IO (StablePtr (Async ()))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Async () -> IO (StablePtr (Async ()))
forall a. a -> IO (StablePtr a)
newStablePtr
    where writeBufN :: CSize -> Ptr a -> IO ()
writeBufN n :: CSize
n s :: Ptr a
s =
              (CSize -> Bool) -> (CSize -> IO CSize) -> CSize -> IO CSize
forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> (a -> m a) -> a -> m a
iterateUntilM (CSize -> CSize -> Bool
forall a. Ord a => a -> a -> Bool
>= CSize
n)
              (\w :: CSize
w -> (CSize
w CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
+) (CSize -> CSize) -> IO CSize -> IO CSize
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                  Fd -> Ptr Word8 -> CSize -> IO CSize
fdWriteBuf Fd
fd (Ptr a -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr a
s (Int -> Ptr Word8) -> Int -> Ptr Word8
forall a b. (a -> b) -> a -> b
$ CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
w) (CSize
n CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
- CSize
w)
                  IO CSize -> (IOError -> IO CSize) -> IO CSize
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError`
                  (\e :: IOError
e -> CSize -> IO CSize
forall (m :: * -> *) a. Monad m => a -> m a
return (CSize -> IO CSize) -> CSize -> IO CSize
forall a b. (a -> b) -> a -> b
$ if IOError -> Bool
isEINTR IOError
e
                                      then 0
                                      else CSize
n CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
+ 1
                  )
              ) 0 IO CSize -> (CSize -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \w :: CSize
w -> Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CSize
w CSize -> CSize -> Bool
forall a. Ord a => a -> a -> Bool
> CSize
n) IO ()
cleanupOnWriteError
          writeFlag1b :: IO ()
writeFlag1b = ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
B.unsafeUseAsCString ByteString
asyncIOFlag1b ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ CSize -> CString -> IO ()
forall a. CSize -> Ptr a -> IO ()
writeBufN 1
          writeFlag8b :: IO ()
writeFlag8b = ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
B.unsafeUseAsCString ByteString
asyncIOFlag8b ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ CSize -> CString -> IO ()
forall a. CSize -> Ptr a -> IO ()
writeBufN 8
          closeChannel :: IO ()
closeChannel = Fd -> IO ()
closeFd Fd
fd IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` IO () -> IOError -> IO ()
forall a b. a -> b -> a
const (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
          -- FIXME: cleanupOnWriteError should free all previously allocated
          -- data and stable pointers. However, leaving this not implemented
          -- seems to be safe because Nginx won't close the event channel or
          -- delete the request object (for request-driven handlers)
          -- regardless of the Haskell handler's duration.
          cleanupOnWriteError :: IO ()
cleanupOnWriteError = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

asyncIOYY :: IOYY -> CString -> CInt ->
    CInt -> CInt -> Ptr CUInt -> CUInt -> CUInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))
asyncIOYY :: IOYY
-> CString
-> CInt
-> CInt
-> CInt
-> Ptr CUInt
-> CUInt
-> CUInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOYY f :: IOYY
f x :: CString
x (I n :: Int
n) fd :: CInt
fd (I fdlk :: Fd
fdlk) active :: Ptr CUInt
active (ToBool efd :: Bool
efd) (ToBool fstRun :: Bool
fstRun) =
    IO (ByteString, Bool)
-> CInt
-> Bool
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOCommon
    (do
        Bool
exiting <- if Bool
fstRun Bool -> Bool -> Bool
&& Fd
fdlk Fd -> Fd -> Bool
forall a. Eq a => a -> a -> Bool
/= -1
                       then (Bool, Bool) -> Bool
forall a b. (a, b) -> b
snd ((Bool, Bool) -> Bool) -> IO (Bool, Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                           ((Bool, Bool) -> Bool) -> IO (Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a. Monad m => (a -> Bool) -> m a -> m a
iterateUntil ((Bool
True Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
==) (Bool -> Bool) -> ((Bool, Bool) -> Bool) -> (Bool, Bool) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool, Bool) -> Bool
forall a b. (a, b) -> a
fst)
                           (Fd -> FileLock -> IO ()
safeWaitToSetLock Fd
fdlk
                                (LockRequest
WriteLock, SeekMode
AbsoluteSeek, 0, 0) IO () -> IO (Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                                    (Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, Bool
False)
                           )
                           IO (Bool, Bool) -> [Handler (Bool, Bool)] -> IO (Bool, Bool)
forall a. IO a -> [Handler a] -> IO a
`catches`
                           [(IOError -> IO (Bool, Bool)) -> Handler (Bool, Bool)
forall a e. Exception e => (e -> IO a) -> Handler a
E.Handler ((IOError -> IO (Bool, Bool)) -> Handler (Bool, Bool))
-> (IOError -> IO (Bool, Bool)) -> Handler (Bool, Bool)
forall a b. (a -> b) -> a -> b
$
                               (Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool, Bool) -> IO (Bool, Bool))
-> (IOError -> (Bool, Bool)) -> IOError -> IO (Bool, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (, Bool
False) (Bool -> (Bool, Bool))
-> (IOError -> Bool) -> IOError -> (Bool, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not (Bool -> Bool) -> (IOError -> Bool) -> IOError -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Bool
isEINTR
                           ,(WorkerProcessIsExiting -> IO (Bool, Bool)) -> Handler (Bool, Bool)
forall a e. Exception e => (e -> IO a) -> Handler a
E.Handler ((WorkerProcessIsExiting -> IO (Bool, Bool))
 -> Handler (Bool, Bool))
-> (WorkerProcessIsExiting -> IO (Bool, Bool))
-> Handler (Bool, Bool)
forall a b. (a -> b) -> a -> b
$
                               (Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool, Bool) -> IO (Bool, Bool))
-> (WorkerProcessIsExiting -> (Bool, Bool))
-> WorkerProcessIsExiting
-> IO (Bool, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool
True, ) (Bool -> (Bool, Bool))
-> (WorkerProcessIsExiting -> Bool)
-> WorkerProcessIsExiting
-> (Bool, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WorkerProcessIsExiting -> WorkerProcessIsExiting -> Bool
forall a. Eq a => a -> a -> Bool
== WorkerProcessIsExiting
WorkerProcessIsExiting)
                           ]
                       else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
        if Bool
exiting
            then (ByteString, Bool) -> IO (ByteString, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
L.empty, Bool
True)
            else do
                Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
fstRun (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CUInt
active 1
                ByteString
x' <- CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
                (, Bool
False) (ByteString -> (ByteString, Bool))
-> IO ByteString -> IO (ByteString, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IOYY
f ByteString
x' Bool
fstRun
    ) CInt
fd Bool
efd

asyncIOYYY :: IOYYY -> Ptr NgxStrType -> Ptr NgxStrType -> CInt ->
    CString -> CInt -> CInt -> CUInt -> Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))
asyncIOYYY :: IOYYY
-> Ptr NgxStrType
-> Ptr NgxStrType
-> CInt
-> CString
-> CInt
-> CInt
-> CUInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOYYY f :: IOYYY
f tmpf :: Ptr NgxStrType
tmpf b :: Ptr NgxStrType
b (I m :: Int
m) x :: CString
x (I n :: Int
n) fd :: CInt
fd (ToBool efd :: Bool
efd) =
    IO (ByteString, Bool)
-> CInt
-> Bool
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOCommon
    (do
        ByteString
b' <- Ptr NgxStrType -> Ptr NgxStrType -> Int -> IO ByteString
peekRequestBodyChunks Ptr NgxStrType
tmpf Ptr NgxStrType
b Int
m
        ByteString
x' <- CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        (, Bool
False) (ByteString -> (ByteString, Bool))
-> IO ByteString -> IO (ByteString, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IOYYY
f ByteString
b' ByteString
x'
    ) CInt
fd Bool
efd

asyncHandler :: AsyncHandler -> CString -> CInt ->
    CInt -> CUInt ->
    Ptr CString -> Ptr CSize -> Ptr (StablePtr B.ByteString) -> Ptr CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))
asyncHandler :: AsyncHandler
-> CString
-> CInt
-> CInt
-> CUInt
-> Ptr CString
-> Ptr CSize
-> Ptr (StablePtr ByteString)
-> Ptr CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncHandler f :: AsyncHandler
f x :: CString
x (I n :: Int
n) fd :: CInt
fd (ToBool efd :: Bool
efd) pct :: Ptr CString
pct plct :: Ptr CSize
plct spct :: Ptr (StablePtr ByteString)
spct pst :: Ptr CInt
pst
        prhs :: Ptr (Ptr NgxStrType)
prhs plrhs :: Ptr CInt
plrhs sprhs :: Ptr (StablePtr ByteString)
sprhs =
    IO (ByteString, Bool)
-> CInt
-> Bool
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOCommon
    (do
        ByteString
x' <- CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        v :: ContentHandlerResult
v@(s :: ByteString
s, ct :: ByteString
ct, I st :: CInt
st, rhs :: HTTPHeaders
rhs) <- AsyncHandler
f ByteString
x'
        (ContentHandlerResult -> IO ContentHandlerResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ContentHandlerResult -> IO ContentHandlerResult)
-> ContentHandlerResult -> IO ContentHandlerResult
forall a b. NFData a => (a -> b) -> a -> b
$!! ContentHandlerResult
v) IO ContentHandlerResult -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO () -> IO ()
forall a. IO a -> IO a
mask_
            (ByteString
-> Ptr CString
-> Ptr CSize
-> Ptr (StablePtr ByteString)
-> Ptr CInt
-> CInt
-> HTTPHeaders
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeAsyncHandlerData ByteString
ct Ptr CString
pct Ptr CSize
plct Ptr (StablePtr ByteString)
spct Ptr CInt
pst CInt
st HTTPHeaders
rhs Ptr (Ptr NgxStrType)
prhs Ptr CInt
plrhs Ptr (StablePtr ByteString)
sprhs)
        (ByteString, Bool) -> IO (ByteString, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
s, Bool
False)
    ) CInt
fd Bool
efd

asyncHandlerRB :: AsyncHandlerRB -> Ptr NgxStrType -> Ptr NgxStrType -> CInt ->
    CString -> CInt -> CInt -> CUInt ->
    Ptr CString -> Ptr CSize -> Ptr (StablePtr B.ByteString) -> Ptr CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) ->
    Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr CUInt -> Ptr (StablePtr L.ByteString) -> IO (StablePtr (Async ()))
asyncHandlerRB :: AsyncHandlerRB
-> Ptr NgxStrType
-> Ptr NgxStrType
-> CInt
-> CString
-> CInt
-> CInt
-> CUInt
-> Ptr CString
-> Ptr CSize
-> Ptr (StablePtr ByteString)
-> Ptr CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncHandlerRB f :: AsyncHandlerRB
f tmpf :: Ptr NgxStrType
tmpf b :: Ptr NgxStrType
b (I m :: Int
m) x :: CString
x (I n :: Int
n) fd :: CInt
fd (ToBool efd :: Bool
efd) pct :: Ptr CString
pct plct :: Ptr CSize
plct spct :: Ptr (StablePtr ByteString)
spct pst :: Ptr CInt
pst
        prhs :: Ptr (Ptr NgxStrType)
prhs plrhs :: Ptr CInt
plrhs sprhs :: Ptr (StablePtr ByteString)
sprhs =
    IO (ByteString, Bool)
-> CInt
-> Bool
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CUInt
-> Ptr (StablePtr ByteString)
-> IO (StablePtr (Async ()))
asyncIOCommon
    (do
        ByteString
b' <- Ptr NgxStrType -> Ptr NgxStrType -> Int -> IO ByteString
peekRequestBodyChunks Ptr NgxStrType
tmpf Ptr NgxStrType
b Int
m
        ByteString
x' <- CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        v :: ContentHandlerResult
v@(s :: ByteString
s, ct :: ByteString
ct, I st :: CInt
st, rhs :: HTTPHeaders
rhs) <- AsyncHandlerRB
f ByteString
b' ByteString
x'
        (ContentHandlerResult -> IO ContentHandlerResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ContentHandlerResult -> IO ContentHandlerResult)
-> ContentHandlerResult -> IO ContentHandlerResult
forall a b. NFData a => (a -> b) -> a -> b
$!! ContentHandlerResult
v) IO ContentHandlerResult -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO () -> IO ()
forall a. IO a -> IO a
mask_
            (ByteString
-> Ptr CString
-> Ptr CSize
-> Ptr (StablePtr ByteString)
-> Ptr CInt
-> CInt
-> HTTPHeaders
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeAsyncHandlerData ByteString
ct Ptr CString
pct Ptr CSize
plct Ptr (StablePtr ByteString)
spct Ptr CInt
pst CInt
st HTTPHeaders
rhs Ptr (Ptr NgxStrType)
prhs Ptr CInt
plrhs Ptr (StablePtr ByteString)
sprhs)
        (ByteString, Bool) -> IO (ByteString, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
s, Bool
False)
    ) CInt
fd Bool
efd

bS :: BS -> CString -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
bS :: BS -> CString -> CInt -> Ptr CString -> Ptr CInt -> IO CUInt
bS f :: BS
f x :: CString
x (I n :: Int
n) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        CUInt
r <- Bool -> CUInt
forall a. Num a => Bool -> a
fromBool (Bool -> CUInt) -> BS -> String -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BS
f (String -> CUInt) -> IO String -> IO CUInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO String
peekCStringLen (CString
x, Int
n)
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
forall a. Ptr a
nullPtr 0 Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
r

bSS :: BSS -> CString -> CInt -> CString -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
bSS :: BSS
-> CString
-> CInt
-> CString
-> CInt
-> Ptr CString
-> Ptr CInt
-> IO CUInt
bSS f :: BSS
f x :: CString
x (I n :: Int
n) y :: CString
y (I m :: Int
m) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        CUInt
r <- (Bool -> CUInt
forall a. Num a => Bool -> a
fromBool (Bool -> CUInt) -> BS -> String -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) (BS -> String -> CUInt) -> BSS -> String -> String -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BSS
f (String -> String -> CUInt) -> IO String -> IO (String -> CUInt)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO String
peekCStringLen (CString
x, Int
n)
                              IO (String -> CUInt) -> IO String -> IO CUInt
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CStringLen -> IO String
peekCStringLen (CString
y, Int
m)
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
forall a. Ptr a
nullPtr 0 Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
r

bLS :: BLS -> Ptr NgxStrType -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
bLS :: BLS
-> Ptr NgxStrType -> CInt -> Ptr CString -> Ptr CInt -> IO CUInt
bLS f :: BLS
f x :: Ptr NgxStrType
x (I n :: Int
n) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        CUInt
r <- Bool -> CUInt
forall a. Num a => Bool -> a
fromBool (Bool -> CUInt) -> BLS -> [String] -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BLS
f ([String] -> CUInt) -> IO [String] -> IO CUInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr NgxStrType -> Int -> IO [String]
peekNgxStringArrayLenLS Ptr NgxStrType
x Int
n
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
forall a. Ptr a
nullPtr 0 Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
r

bY :: BY -> CString -> CInt ->
    Ptr CString -> Ptr CInt -> IO CUInt
bY :: (ByteString -> Bool)
-> CString -> CInt -> Ptr CString -> Ptr CInt -> IO CUInt
bY f :: ByteString -> Bool
f x :: CString
x (I n :: Int
n) p :: Ptr CString
p pl :: Ptr CInt
pl =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
p Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        CUInt
r <- Bool -> CUInt
forall a. Num a => Bool -> a
fromBool (Bool -> CUInt) -> (ByteString -> Bool) -> ByteString -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Bool
f (ByteString -> CUInt) -> IO ByteString -> IO CUInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        CString -> CInt -> Ptr CString -> Ptr CInt -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
forall a. Ptr a
nullPtr 0 Ptr CString
p Ptr CInt
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
r

handler :: Handler -> CString -> CInt -> Ptr (Ptr NgxStrType) -> Ptr CInt ->
    Ptr CString -> Ptr CSize -> Ptr (StablePtr B.ByteString) -> Ptr CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr (StablePtr L.ByteString) ->
    Ptr (StablePtr L.ByteString) -> IO CUInt
handler :: Handler
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CString
-> Ptr CSize
-> Ptr (StablePtr ByteString)
-> Ptr CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> Ptr (StablePtr ByteString)
-> IO CUInt
handler f :: Handler
f x :: CString
x (I n :: Int
n) p :: Ptr (Ptr NgxStrType)
p pl :: Ptr CInt
pl pct :: Ptr CString
pct plct :: Ptr CSize
plct spct :: Ptr (StablePtr ByteString)
spct pst :: Ptr CInt
pst prhs :: Ptr (Ptr NgxStrType)
prhs plrhs :: Ptr CInt
plrhs sprhs :: Ptr (StablePtr ByteString)
sprhs spd :: Ptr (StablePtr ByteString)
spd =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
pct Ptr CInt
pst (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        v :: ContentHandlerResult
v@(s :: ByteString
s, ct :: ByteString
ct, I st :: CInt
st, rhs :: HTTPHeaders
rhs) <- Handler
f Handler -> IO ByteString -> IO ContentHandlerResult
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        CSize
lct <- (ContentHandlerResult -> IO ContentHandlerResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ContentHandlerResult -> IO ContentHandlerResult)
-> ContentHandlerResult -> IO ContentHandlerResult
forall a b. NFData a => (a -> b) -> a -> b
$!! ContentHandlerResult
v) IO ContentHandlerResult -> IO CSize -> IO CSize
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ByteString
-> Ptr CString -> Ptr CSize -> Ptr CInt -> CInt -> IO CSize
pokeContentTypeAndStatus ByteString
ct Ptr CString
pct Ptr CSize
plct Ptr CInt
pst CInt
st
        (CSize -> IO CSize
forall (m :: * -> *) a. Monad m => a -> m a
return (CSize -> IO CSize) -> CSize -> IO CSize
forall a b. NFData a => (a -> b) -> a -> b
$!! CSize
lct) IO CSize -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
            ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString (HTTPHeaders -> ByteString
fromHTTPHeaders HTTPHeaders
rhs) Ptr (Ptr NgxStrType)
prhs Ptr CInt
plrhs Ptr (StablePtr ByteString)
sprhs
        ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString ByteString
s Ptr (Ptr NgxStrType)
p Ptr CInt
pl Ptr (StablePtr ByteString)
spd
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CSize
lct CSize -> CSize -> Bool
forall a. Ord a => a -> a -> Bool
> 0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> IO (StablePtr ByteString)
forall a. a -> IO (StablePtr a)
newStablePtr ByteString
ct IO (StablePtr ByteString)
-> (StablePtr ByteString -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr (StablePtr ByteString) -> StablePtr ByteString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (StablePtr ByteString)
spct
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 0

defHandler :: YY -> CString -> CInt ->
    Ptr (Ptr NgxStrType) -> Ptr CInt -> Ptr CString ->
    Ptr (StablePtr L.ByteString) -> IO CUInt
defHandler :: YY
-> CString
-> CInt
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr CString
-> Ptr (StablePtr ByteString)
-> IO CUInt
defHandler f :: YY
f x :: CString
x (I n :: Int
n) p :: Ptr (Ptr NgxStrType)
p pl :: Ptr CInt
pl pe :: Ptr CString
pe spd :: Ptr (StablePtr ByteString)
spd =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
pe Ptr CInt
pl (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        ByteString
s <- YY
f YY -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        ByteString
-> Ptr (Ptr NgxStrType)
-> Ptr CInt
-> Ptr (StablePtr ByteString)
-> IO ()
pokeLazyByteString ByteString
s Ptr (Ptr NgxStrType)
p Ptr CInt
pl Ptr (StablePtr ByteString)
spd
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 0

unsafeHandler :: UnsafeHandler -> CString -> CInt -> Ptr CString -> Ptr CSize ->
    Ptr CString -> Ptr CSize -> Ptr CInt -> IO CUInt
unsafeHandler :: UnsafeHandler
-> CString
-> CInt
-> Ptr CString
-> Ptr CSize
-> Ptr CString
-> Ptr CSize
-> Ptr CInt
-> IO CUInt
unsafeHandler f :: UnsafeHandler
f x :: CString
x (I n :: Int
n) p :: Ptr CString
p pl :: Ptr CSize
pl pct :: Ptr CString
pct plct :: Ptr CSize
plct pst :: Ptr CInt
pst =
    Ptr CString -> Ptr CInt -> IO CUInt -> IO CUInt
safeHandler Ptr CString
pct Ptr CInt
pst (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$ do
        v :: UnsafeContentHandlerResult
v@(s :: ByteString
s, ct :: ByteString
ct, I st :: CInt
st) <- UnsafeHandler
f UnsafeHandler -> IO ByteString -> IO UnsafeContentHandlerResult
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
B.unsafePackCStringLen (CString
x, Int
n)
        (UnsafeContentHandlerResult -> IO UnsafeContentHandlerResult
forall (m :: * -> *) a. Monad m => a -> m a
return (UnsafeContentHandlerResult -> IO UnsafeContentHandlerResult)
-> UnsafeContentHandlerResult -> IO UnsafeContentHandlerResult
forall a b. NFData a => (a -> b) -> a -> b
$!! UnsafeContentHandlerResult
v) IO UnsafeContentHandlerResult -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO CSize -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ByteString
-> Ptr CString -> Ptr CSize -> Ptr CInt -> CInt -> IO CSize
pokeContentTypeAndStatus ByteString
ct Ptr CString
pct Ptr CSize
plct Ptr CInt
pst CInt
st)
        PtrLen t :: CString
t l :: CSize
l <- ByteString -> (CStringLen -> IO CStringLen) -> IO CStringLen
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
s CStringLen -> IO CStringLen
forall (m :: * -> *) a. Monad m => a -> m a
return
        CString -> CSize -> Ptr CString -> Ptr CSize -> IO ()
forall a.
Storable a =>
CString -> a -> Ptr CString -> Ptr a -> IO ()
pokeCStringLen CString
t CSize
l Ptr CString
p Ptr CSize
pl
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return 0

{- SPLICE: safe version of waitToSetLock as defined in System.Posix.IO -}

foreign import ccall interruptible "HsBase.h fcntl"
    safe_c_fcntl_lock :: CInt -> CInt -> Ptr CFLock -> IO CInt

mode2Int :: SeekMode -> CShort
mode2Int :: SeekMode -> CShort
mode2Int AbsoluteSeek = 0
mode2Int RelativeSeek = 1
mode2Int SeekFromEnd  = 2

lockReq2Int :: LockRequest -> CShort
lockReq2Int :: LockRequest -> CShort
lockReq2Int ReadLock  = 0
lockReq2Int WriteLock = 1
lockReq2Int Unlock    = 2

allocaLock :: FileLock -> (Ptr CFLock -> IO a) -> IO a
allocaLock :: FileLock -> (Ptr CFLock -> IO a) -> IO a
allocaLock (lockreq :: LockRequest
lockreq, mode :: SeekMode
mode, start :: FileOffset
start, len :: FileOffset
len) io :: Ptr CFLock -> IO a
io =
    Int -> (Ptr CFLock -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes 32 ((Ptr CFLock -> IO a) -> IO a) -> (Ptr CFLock -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \p :: Ptr CFLock
p -> do
        (Ptr CFLock -> Int -> CShort -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
`pokeByteOff`  0) Ptr CFLock
p (LockRequest -> CShort
lockReq2Int LockRequest
lockreq)
        (Ptr CFLock -> Int -> CShort -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
`pokeByteOff`  2) Ptr CFLock
p (SeekMode -> CShort
mode2Int SeekMode
mode)
        (Ptr CFLock -> Int -> FileOffset -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
`pokeByteOff`  8) Ptr CFLock
p FileOffset
start
        (Ptr CFLock -> Int -> FileOffset -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
`pokeByteOff` 16) Ptr CFLock
p FileOffset
len
        Ptr CFLock -> IO a
io Ptr CFLock
p

safeWaitToSetLock :: Fd -> FileLock -> IO ()
safeWaitToSetLock :: Fd -> FileLock -> IO ()
safeWaitToSetLock (Fd fd :: CInt
fd) lock :: FileLock
lock = FileLock -> (Ptr CFLock -> IO ()) -> IO ()
forall a. FileLock -> (Ptr CFLock -> IO a) -> IO a
allocaLock FileLock
lock ((Ptr CFLock -> IO ()) -> IO ()) -> (Ptr CFLock -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
    \p_flock :: Ptr CFLock
p_flock -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ "safeWaitToSetLock" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
        CInt -> CInt -> Ptr CFLock -> IO CInt
safe_c_fcntl_lock CInt
fd 7 Ptr CFLock
p_flock

{- SPLICE: END -}

foreign export ccall ngxExportInstallSignalHandler :: IO ()
ngxExportInstallSignalHandler :: IO ()
ngxExportInstallSignalHandler :: IO ()
ngxExportInstallSignalHandler = IO Handler -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Handler -> IO ()) -> IO Handler -> IO ()
forall a b. (a -> b) -> a -> b
$
    CInt -> Handler -> Maybe SignalSet -> IO Handler
installHandler CInt
keyboardSignal Handler
Ignore Maybe SignalSet
forall a. Maybe a
Nothing

foreign export ccall ngxExportTerminateTask ::
    StablePtr (Async ()) -> IO ()
ngxExportTerminateTask ::
    StablePtr (Async ()) -> IO ()
ngxExportTerminateTask :: StablePtr (Async ()) -> IO ()
ngxExportTerminateTask = StablePtr (Async ()) -> IO (Async ())
forall a. StablePtr a -> IO a
deRefStablePtr (StablePtr (Async ()) -> IO (Async ()))
-> (Async () -> IO ()) -> StablePtr (Async ()) -> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
    (Async () -> WorkerProcessIsExiting -> IO ())
-> WorkerProcessIsExiting -> Async () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Async () -> WorkerProcessIsExiting -> IO ()
forall e a. Exception e => Async a -> e -> IO ()
cancelWith WorkerProcessIsExiting
WorkerProcessIsExiting

foreign export ccall ngxExportServiceHookInterrupt ::
    StablePtr (Async ()) -> IO ()
ngxExportServiceHookInterrupt ::
    StablePtr (Async ()) -> IO ()
ngxExportServiceHookInterrupt :: StablePtr (Async ()) -> IO ()
ngxExportServiceHookInterrupt = StablePtr (Async ()) -> IO (Async ())
forall a. StablePtr a -> IO a
deRefStablePtr (StablePtr (Async ()) -> IO (Async ()))
-> (Async () -> IO ()) -> StablePtr (Async ()) -> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
    (ThreadId -> ServiceHookInterrupt -> IO ())
-> ServiceHookInterrupt -> ThreadId -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip ThreadId -> ServiceHookInterrupt -> IO ()
forall e. Exception e => ThreadId -> e -> IO ()
throwTo ServiceHookInterrupt
ServiceHookInterrupt (ThreadId -> IO ()) -> (Async () -> ThreadId) -> Async () -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async () -> ThreadId
forall a. Async a -> ThreadId
asyncThreadId

foreign export ccall ngxExportVersion ::
    Ptr CInt -> CInt -> IO CInt
ngxExportVersion ::
    Ptr CInt -> CInt -> IO CInt
ngxExportVersion :: Ptr CInt -> CInt -> IO CInt
ngxExportVersion x :: Ptr CInt
x (I n :: Int
n) = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> IO Int -> IO CInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
    (Int -> Int -> IO Int) -> Int -> [Int] -> IO Int
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\k :: Int
k (I v :: CInt
v) -> Ptr CInt -> Int -> CInt -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CInt
x Int
k CInt
v IO () -> IO Int -> IO Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1)) 0
        (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
n ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ Version -> [Int]
versionBranch Version
version)

-- | 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).
ngxCyclePtr :: IO (Ptr ())
ngxCyclePtr :: IO (Ptr ())
ngxCyclePtr = IORef (Ptr ()) -> IO (Ptr ())
forall a. IORef a -> IO a
readIORef IORef (Ptr ())
ngxCyclePtrStore

-- | 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).
ngxUpstreamMainConfPtr :: IO (Ptr ())
ngxUpstreamMainConfPtr :: IO (Ptr ())
ngxUpstreamMainConfPtr = IORef (Ptr ()) -> IO (Ptr ())
forall a. IORef a -> IO a
readIORef IORef (Ptr ())
ngxUpstreamMainConfPtrStore

-- | 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/__).
ngxCachedTimePtr :: IO (Ptr (Ptr ()))
ngxCachedTimePtr :: IO (Ptr (Ptr ()))
ngxCachedTimePtr = IORef (Ptr (Ptr ())) -> IO (Ptr (Ptr ()))
forall a. IORef a -> IO a
readIORef IORef (Ptr (Ptr ()))
ngxCachedTimePtrStore

-- | Returns the /PID/ of the current worker process cached in Nginx.
--
-- @since 1.7.1
ngxCachedPid :: IO CPid
ngxCachedPid :: IO CPid
ngxCachedPid = IORef CPid -> IO CPid
forall a. IORef a -> IO a
readIORef IORef CPid
ngxCachedPidStore

foreign export ccall ngxExportSetCyclePtr :: Ptr () -> IO ()
ngxExportSetCyclePtr :: Ptr () -> IO ()
ngxExportSetCyclePtr :: Ptr () -> IO ()
ngxExportSetCyclePtr = IORef (Ptr ()) -> Ptr () -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Ptr ())
ngxCyclePtrStore

foreign export ccall ngxExportSetUpstreamMainConfPtr :: Ptr () -> IO ()
ngxExportSetUpstreamMainConfPtr :: Ptr () -> IO ()
ngxExportSetUpstreamMainConfPtr :: Ptr () -> IO ()
ngxExportSetUpstreamMainConfPtr = IORef (Ptr ()) -> Ptr () -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Ptr ())
ngxUpstreamMainConfPtrStore

foreign export ccall ngxExportSetCachedTimePtr :: Ptr (Ptr ()) -> IO ()
ngxExportSetCachedTimePtr :: Ptr (Ptr ()) -> IO ()
ngxExportSetCachedTimePtr :: Ptr (Ptr ()) -> IO ()
ngxExportSetCachedTimePtr = IORef (Ptr (Ptr ())) -> Ptr (Ptr ()) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Ptr (Ptr ()))
ngxCachedTimePtrStore

foreign export ccall ngxExportSetCachedPid :: CPid -> IO ()
ngxExportSetCachedPid :: CPid -> IO ()
ngxExportSetCachedPid :: CPid -> IO ()
ngxExportSetCachedPid = IORef CPid -> CPid -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef CPid
ngxCachedPidStore

ngxCyclePtrStore :: IORef (Ptr ())
ngxCyclePtrStore :: IORef (Ptr ())
ngxCyclePtrStore = IO (IORef (Ptr ())) -> IORef (Ptr ())
forall a. IO a -> a
unsafePerformIO (IO (IORef (Ptr ())) -> IORef (Ptr ()))
-> IO (IORef (Ptr ())) -> IORef (Ptr ())
forall a b. (a -> b) -> a -> b
$ Ptr () -> IO (IORef (Ptr ()))
forall a. a -> IO (IORef a)
newIORef Ptr ()
forall a. Ptr a
nullPtr
{-# NOINLINE ngxCyclePtrStore #-}

ngxUpstreamMainConfPtrStore :: IORef (Ptr ())
ngxUpstreamMainConfPtrStore :: IORef (Ptr ())
ngxUpstreamMainConfPtrStore = IO (IORef (Ptr ())) -> IORef (Ptr ())
forall a. IO a -> a
unsafePerformIO (IO (IORef (Ptr ())) -> IORef (Ptr ()))
-> IO (IORef (Ptr ())) -> IORef (Ptr ())
forall a b. (a -> b) -> a -> b
$ Ptr () -> IO (IORef (Ptr ()))
forall a. a -> IO (IORef a)
newIORef Ptr ()
forall a. Ptr a
nullPtr
{-# NOINLINE ngxUpstreamMainConfPtrStore #-}

ngxCachedTimePtrStore :: IORef (Ptr (Ptr ()))
ngxCachedTimePtrStore :: IORef (Ptr (Ptr ()))
ngxCachedTimePtrStore = IO (IORef (Ptr (Ptr ()))) -> IORef (Ptr (Ptr ()))
forall a. IO a -> a
unsafePerformIO (IO (IORef (Ptr (Ptr ()))) -> IORef (Ptr (Ptr ())))
-> IO (IORef (Ptr (Ptr ()))) -> IORef (Ptr (Ptr ()))
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> IO (IORef (Ptr (Ptr ())))
forall a. a -> IO (IORef a)
newIORef Ptr (Ptr ())
forall a. Ptr a
nullPtr
{-# NOINLINE ngxCachedTimePtrStore #-}

ngxCachedPidStore :: IORef CPid
ngxCachedPidStore :: IORef CPid
ngxCachedPidStore = IO (IORef CPid) -> IORef CPid
forall a. IO a -> a
unsafePerformIO (IO (IORef CPid) -> IORef CPid) -> IO (IORef CPid) -> IORef CPid
forall a b. (a -> b) -> a -> b
$ CPid -> IO (IORef CPid)
forall a. a -> IO (IORef a)
newIORef (-1)
{-# NOINLINE ngxCachedPidStore #-}