ngx-export-1.2.2: Helper module for Nginx haskell module

Copyright(c) Alexey Radkov 2016-2018
LicenseBSD-style
Maintaineralexey.radkov@gmail.com
Stabilitystable
Portabilitynon-portable (requires POSIX)
Safe HaskellNone
LanguageHaskell98

NgxExport

Contents

Description

Export regular haskell functions for using in directives of nginx-haskell-module.

Synopsis

Type declarations

type ContentHandlerResult = (ByteString, ByteString, Int) Source #

The first element of the 3-tuple is content, the second is content type, and the third is HTTP status.

type UnsafeContentHandlerResult = (ByteString, ByteString, Int) Source #

The first element of the 3-tuple is content, the second is content type, and the third is HTTP status. Both the content and the content type are supposed to be referring to low-level string literals which do not need to be freed upon request termination and must not be garbage-collected in the Haskell RTS.

Exporters

ngxExportSS :: Name -> Q [Dec] Source #

Exports a function of type String -> String for using in directive haskell_run.

ngxExportSSS :: Name -> Q [Dec] Source #

Exports a function of type String -> String -> String for using in directive haskell_run.

ngxExportSLS :: Name -> Q [Dec] Source #

Exports a function of type [String] -> String for using in directive haskell_run.

ngxExportBS :: Name -> Q [Dec] Source #

Exports a function of type String -> Bool for using in directive haskell_run.

ngxExportBSS :: Name -> Q [Dec] Source #

Exports a function of type String -> String -> Bool for using in directive haskell_run.

ngxExportBLS :: Name -> Q [Dec] Source #

Exports a function of type [String] -> Bool for using in directive haskell_run.

ngxExportYY :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> ByteString for using in directive haskell_run.

ngxExportBY :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> Bool for using in directive haskell_run.

ngxExportIOYY :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> IO ByteString for using in directive haskell_run.

ngxExportAsyncIOYY :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> IO ByteString for using in directive haskell_run_async.

ngxExportAsyncOnReqBody :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> ByteString -> IO ByteString for using in directive haskell_run_async_on_request_body.

The first argument of the exported function contains buffers of the client request body.

ngxExportServiceIOYY :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> Bool -> IO ByteString for using in directive haskell_run_service.

The boolean argument of the exported function marks that the service is being run for the first time.

ngxExportHandler :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> ContentHandlerResult for using in directives haskell_content and haskell_static_content.

ngxExportDefHandler :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> ByteString for using in directives haskell_content and haskell_static_content.

ngxExportUnsafeHandler :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> UnsafeContentHandlerResult for using in directive haskell_unsafe_content.

ngxExportAsyncHandler :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> IO ContentHandlerResult for using in directive haskell_async_content.

ngxExportAsyncHandlerOnReqBody :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> ByteString -> IO ContentHandlerResult for using in directive haskell_async_content_on_request_body.

The first argument of the exported function contains buffers of the client request body.

ngxExportServiceHook :: Name -> Q [Dec] Source #

Exports a function of type ByteString -> IO ByteString for using in directive haskell_service_hook.

Re-exported data constructors from Foreign.C

newtype CInt :: * #

Haskell type representing the C int type.

Constructors

CInt Int32 

Instances

Bounded CInt 
Enum CInt 

Methods

succ :: CInt -> CInt #

pred :: CInt -> CInt #

toEnum :: Int -> CInt #

fromEnum :: CInt -> Int #

enumFrom :: CInt -> [CInt] #

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

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

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

Eq CInt 

Methods

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

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

Integral CInt 

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

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

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

toInteger :: CInt -> Integer #

Num CInt 

Methods

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

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

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

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Ord CInt 

Methods

compare :: CInt -> CInt -> Ordering #

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

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

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

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

max :: CInt -> CInt -> CInt #

min :: CInt -> CInt -> CInt #

Read CInt 
Real CInt 

Methods

toRational :: CInt -> Rational #

Show CInt 

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

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

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

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

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

peek :: Ptr CInt -> IO CInt #

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

Bits CInt 
FiniteBits CInt 
NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

newtype CUInt :: * #

Haskell type representing the C unsigned int type.

Constructors

CUInt Word32 

Instances

Bounded CUInt 
Enum CUInt 
Eq CUInt 

Methods

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

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

Integral CUInt 
Num CUInt 
Ord CUInt 

Methods

compare :: CUInt -> CUInt -> Ordering #

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

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

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

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

max :: CUInt -> CUInt -> CUInt #

min :: CUInt -> CUInt -> CUInt #

Read CUInt 
Real CUInt 

Methods

toRational :: CUInt -> Rational #

Show CUInt 

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Storable CUInt 

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

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

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

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

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

peek :: Ptr CUInt -> IO CUInt #

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

Bits CUInt 
FiniteBits CUInt 
NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #