Add 'wai-handler-scgi/' from commit '29039323c8ef9cf4b24cbae4aaafe20b9a590f9d'

git-subtree-dir: wai-handler-scgi
git-subtree-mainline: 2362c7fe79
git-subtree-split: 29039323c8
This commit is contained in:
Michael Snoyman 2011-07-22 16:52:22 +03:00
commit 745eba8d63
7 changed files with 190 additions and 0 deletions

25
wai-handler-scgi/LICENSE Normal file
View File

@ -0,0 +1,25 @@
The following license covers this documentation, and the source code, except
where otherwise indicated.
Copyright 2010, Michael Snoyman. All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:
* Redistributions of source code must retain the above copyright notice, this
list of conditions and the following disclaimer.
* Redistributions in binary form must reproduce the above copyright notice,
this list of conditions and the following disclaimer in the documentation
and/or other materials provided with the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS "AS IS" AND ANY EXPRESS OR
IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO
EVENT SHALL THE COPYRIGHT HOLDERS BE LIABLE FOR ANY DIRECT, INDIRECT,
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA,
OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE
OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF
ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.

View File

@ -0,0 +1,96 @@
{-# LANGUAGE ForeignFunctionInterface #-}
module Network.Wai.Handler.SCGI
( run
, runSendfile
) where
import Network.Wai
import Network.Wai.Handler.CGI (runGeneric, requestBodyFunc)
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.C
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import qualified Data.ByteString.Unsafe as S
import qualified Data.ByteString.Char8 as S8
import Data.IORef
import Data.ByteString.Lazy.Internal (defaultChunkSize)
run :: Application -> IO ()
run app = runOne Nothing app >> run app
runSendfile :: ByteString -> Application -> IO ()
runSendfile sf app = runOne (Just sf) app >> runSendfile sf app
runOne :: Maybe ByteString -> Application -> IO ()
runOne sf app = do
socket <- c'accept 0 nullPtr nullPtr
headersBS <- readNetstring socket
let headers@((_, conLenS):_) = parseHeaders $ S.split 0 headersBS
let conLen = case reads conLenS of
(i, _):_ -> i
[] -> 0
conLenI <- newIORef conLen
runGeneric headers (requestBodyFunc $ input socket conLenI)
(write socket) sf app
drain socket conLenI
_ <- c'close socket
return ()
write :: CInt -> S.ByteString -> IO ()
write socket bs = S.unsafeUseAsCStringLen bs $ \(s, l) -> do
_ <- c'write socket s (fromIntegral l)
return ()
input :: CInt -> IORef Int -> Int -> IO (Maybe S.ByteString)
input socket ilen rlen = do
len <- readIORef ilen
case len of
0 -> return Nothing
_ -> do
bs <- readByteString socket
$ minimum [defaultChunkSize, len, rlen]
writeIORef ilen $ len - S.length bs
return $ Just bs
drain :: CInt -> IORef Int -> IO () -- FIXME do it in chunks
drain socket ilen = do
len <- readIORef ilen
_ <- readByteString socket len
return ()
parseHeaders :: [S.ByteString] -> [(String, String)]
parseHeaders (x:y:z) = (S8.unpack x, S8.unpack y) : parseHeaders z
parseHeaders _ = []
readNetstring :: CInt -> IO S.ByteString
readNetstring socket = do
len <- readLen 0
bs <- readByteString socket len
_ <- readByteString socket 1 -- the comma
return bs
where
readLen l = do
bs <- readByteString socket 1
let [c] = S8.unpack bs
if c == ':'
then return l
else readLen $ l * 10 + (fromEnum c - fromEnum '0')
readByteString :: CInt -> Int -> IO S.ByteString
readByteString socket len = do
buf <- mallocBytes len
_ <- c'read socket buf $ fromIntegral len
S.unsafePackCStringFinalizer (castPtr buf) len $ free buf
foreign import ccall unsafe "accept"
c'accept :: CInt -> Ptr a -> Ptr a -> IO CInt
foreign import ccall unsafe "close"
c'close :: CInt -> IO CInt
foreign import ccall unsafe "write"
c'write :: CInt -> Ptr CChar -> CInt -> IO CInt
foreign import ccall unsafe "read"
c'read :: CInt -> Ptr CChar -> CInt -> IO CInt

0
wai-handler-scgi/README Normal file
View File

7
wai-handler-scgi/Setup.lhs Executable file
View File

@ -0,0 +1,7 @@
#!/usr/bin/env runhaskell
> module Main where
> import Distribution.Simple
> main :: IO ()
> main = defaultMain

View File

@ -0,0 +1,19 @@
# Run with lighttpd -D -f lighttpd.conf
server.port = 3000
server.document-root = "."
server.modules = ("mod_scgi", "mod_rewrite")
url.rewrite-once = (
"(.*)" => "/app/$1"
)
scgi.server = (
"/app" => ((
"socket" => "/tmp/test.scgi.socket",
"check-local" => "disable",
"bin-path" => "./test",
"min-procs" => 1,
"max-procs" => 12,
"idle-timeout" => 30
))
)

19
wai-handler-scgi/test.hs Normal file
View File

@ -0,0 +1,19 @@
{-# LANGUAGE OverloadedStrings #-}
import Network.Wai
import Network.Wai.Handler.SCGI
import Control.Monad.IO.Class
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as L8
import qualified Data.Enumerator as E
main = run app
app req
| pathInfo req == "/" = return $ responseLBS status200 [("Content-Type", "text/html")] "<form method='post' action='/post'><input type='text' name='name'><input type='submit'></form>"
app req = do
bss <- E.consume
return $ responseLBS status200 [("Content-Type", "text/plain")] $ L.concat
[ L8.pack $ show $ requestHeaders req
, "\n"
, L.fromChunks bss
]

View File

@ -0,0 +1,24 @@
name: wai-handler-scgi
version: 0.4.0
license: BSD3
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>
maintainer: Michael Snoyman <michael@snoyman.com>
synopsis: Wai handler to SCGI
category: Web
stability: stable
cabal-version: >= 1.6
build-type: Simple
homepage: http://github.com/snoyberg/wai-handler-scgi
library
build-depends: base >= 4 && < 5
, wai >= 0.4 && < 0.5
, wai-extra >= 0.4 && < 0.5
, bytestring >= 0.9.1.4 && < 0.10
exposed-modules: Network.Wai.Handler.SCGI
ghc-options: -Wall
source-repository head
type: git
location: git://github.com/snoyberg/wai-handler-scgi.git