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

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

NgxExport

Contents

Description

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

Synopsis

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 -> (ByteString, String, Int) for using in directives haskell_content and haskell_static_content.

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

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 -> (ByteString, ByteString, Int) for using in directive haskell_unsafe_content.

The first element in the returned 3-tuple of the exported function is the content, the second is the content type, and the third is the 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 the request termination and must not be garbage-collected in the Haskell RTS.

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 

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