[web-devel] wai-logger
Kazu Yamamoto ( 山本和彦 )
kazu at iij.ad.jp
Fri Aug 19 07:30:30 CEST 2011
Hello,
> 2. Would it make sense to use a Builder (from blaze-builder) in place
> of LogStr? Though based on the black magic you have going on under the
> surface there, I'm guessing you did it this way for a reason ;).
I have implemented a Builder version:
git://github.com/kazu-yamamoto/wai-logger.git
branch: blaze
Attached code shows how to use this version.
Please read the implementation of hPutBuilder:
https://github.com/kazu-yamamoto/wai-logger/blob/blaze/Network/Wai/Logger/IO.hs
In this version, I guess that intermediate ByteString is not fused, so
one unnecessary intermediate ByteString is created with
toByteString. Thus, this version is slower than the original. Since
I'm a beginner of blaze-builder, I don't know how we can directly copy
Builder to Handle's buffer. Suggestions would be appreciated.
--Kazu
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Blaze.ByteString.Builder (fromByteString)
import Control.Monad.IO.Class (liftIO)
import Data.ByteString.Char8
import Network.HTTP.Types (status200)
import Network.Wai
import Network.Wai.Handler.Warp
import Network.Wai.Logger
import System.IO
main :: IO ()
main = do
initHandle stdout -- set blockBuffering
dref <- dateInit
run 3000 $ logApp dref
logApp :: DateRef -> Application
logApp dref req = do
date <- liftIO $ getDate dref
let status = status200
len = 4
liftIO $ hPutBuilder stdout $ apacheFormatBuilder date req status (Just len)
liftIO $ hFlush stdout -- delete here to see if block buffered
return $ ResponseBuilder status
[("Content-Type", "text/plain")
,("Content-Length", pack (show len))]
$ fromByteString "PONG"
More information about the web-devel
mailing list