Skip to content

Commit

Permalink
Style nazi strikes again.
Browse files Browse the repository at this point in the history
  • Loading branch information
mightybyte committed Oct 28, 2011
1 parent e28d284 commit 4717e49
Show file tree
Hide file tree
Showing 8 changed files with 51 additions and 44 deletions.
12 changes: 6 additions & 6 deletions src/Snap/Internal/Http/Types.hs
Expand Up @@ -252,11 +252,11 @@ data Request = Request
-- value of 'rqPathInfo' will be @\"bar\"@.
, rqPathInfo :: !ByteString

-- | The \"context path\" of the request; catenating 'rqContextPath', and
-- 'rqPathInfo' should get you back to the original 'rqURI' (ignoring
-- query strings). The 'rqContextPath' always begins and ends with a
-- slash (@\"\/\"@) character, and represents the path (relative to your
-- component\/snaplet) you took to get to your handler.
-- | The \"context path\" of the request; catenating 'rqContextPath',
-- and 'rqPathInfo' should get you back to the original 'rqURI'
-- (ignoring query strings). The 'rqContextPath' always begins and ends
-- with a slash (@\"\/\"@) character, and represents the path (relative
-- to your component\/snaplet) you took to get to your handler.
, rqContextPath :: !ByteString

-- | Returns the @URI@ requested by the client.
Expand Down Expand Up @@ -423,7 +423,7 @@ instance Show Response where

statusline = concat [ "HTTP/"
, show v1
, "."
, "."
, show v2
, " "
, show $ rspStatus r
Expand Down
5 changes: 3 additions & 2 deletions src/Snap/Internal/Iteratee/BoyerMooreHorspool.hs
Expand Up @@ -127,7 +127,8 @@ bmhEnumeratee needle _step = do
let !aftermatch = S.drop (hend+1) haystack

step <- if not $ S.null nomatch
then lift $ runIteratee $ k $ Chunks [NoMatch nomatch]
then lift $ runIteratee $ k
$ Chunks [NoMatch nomatch]
else return $ Continue k

cDone step $ \k' -> do
Expand All @@ -144,7 +145,7 @@ bmhEnumeratee needle _step = do
mkCoeff hidx = let !ll = hlen - hidx
!nm = nlen - ll
in (ll,nm)

crossBound !hidx0 = {-# SCC "crossBound" #-} do
let (!leftLen, needMore) = mkCoeff hidx0

Expand Down
12 changes: 6 additions & 6 deletions src/Snap/Internal/Test/Assertions.hs
Expand Up @@ -39,9 +39,9 @@ assert404 rsp = assertEqual message 404 status


------------------------------------------------------------------------------
-- | Given a Response, asserts that its HTTP status code is between 300 and 399
-- (a redirect), and that the Location header of the Response points to the
-- specified URI.
-- | Given a Response, asserts that its HTTP status code is between 300 and
-- 399 (a redirect), and that the Location header of the Response points to
-- the specified URI.
assertRedirectTo :: ByteString -- ^ The Response should redirect to this
-- URI
-> Response
Expand All @@ -58,8 +58,8 @@ assertRedirectTo uri rsp = do


------------------------------------------------------------------------------
-- | Given a Response, asserts that its HTTP status code is between 300 and 399
-- (a redirect).
-- | Given a Response, asserts that its HTTP status code is between 300 and
-- 399 (a redirect).
assertRedirect :: Response -> Assertion
assertRedirect rsp = assertBool message (300 <= status && status <= 399)
where
Expand All @@ -71,7 +71,7 @@ assertRedirect rsp = assertBool message (300 <= status && status <= 399)
------------------------------------------------------------------------------
-- | Given a Response, asserts that its body matches the given regular
-- expression.
assertBodyContains :: ByteString -- ^ Regexp that will match the body content
assertBodyContains :: ByteString -- ^ Regexp that will match the body content
-> Response
-> Assertion
assertBodyContains match rsp = do
Expand Down
36 changes: 19 additions & 17 deletions src/Snap/Internal/Test/RequestBuilder.hs
Expand Up @@ -105,7 +105,8 @@ buildRequest mm = do

fixupMethod = do
rq <- rGet
if (rqMethod rq == GET || rqMethod rq == DELETE || rqMethod rq == HEAD)
if (rqMethod rq == GET || rqMethod rq == DELETE ||
rqMethod rq == HEAD)
then do
-- These requests are not permitted to have bodies
let rq' = deleteHeader "Content-Type" rq
Expand All @@ -116,7 +117,8 @@ buildRequest mm = do
fixupCL = do
rq <- rGet
maybe (rPut $ deleteHeader "Content-Length" rq)
(\cl -> rPut $ H.setHeader "Content-Length" (S.pack (show cl)) rq)
(\cl -> rPut $ H.setHeader "Content-Length"
(S.pack (show cl)) rq)
(rqContentLength rq)

fixupParams = do
Expand All @@ -134,7 +136,7 @@ buildRequest mm = do

rPut $ rq { rqParams = Map.unionWith (++) pms post }

-------------------------------------------------------------------------------
------------------------------------------------------------------------------
-- | A request body of type \"@multipart/form-data@\" consists of a set of
-- named form parameters, each of which can by either a list of regular form
-- values or a set of file uploads.
Expand All @@ -160,10 +162,10 @@ data FileData = FileData {


------------------------------------------------------------------------------
-- | The 'RequestType' datatype enumerates the different kinds of HTTP requests
-- you can generate using the testing interface. Most users will prefer to use
-- the 'get', 'postUrlEncoded', 'postMultipart', 'put', and 'delete'
-- convenience functions.
-- | The 'RequestType' datatype enumerates the different kinds of HTTP
-- requests you can generate using the testing interface. Most users will
-- prefer to use the 'get', 'postUrlEncoded', 'postMultipart', 'put', and
-- 'delete' convenience functions.
data RequestType
= GetRequest
| RequestWithRawBody Method ByteString
Expand Down Expand Up @@ -357,9 +359,9 @@ fixupURI = do


------------------------------------------------------------------------------
-- | Sets the request's query string to be the raw bytestring provided, without
-- any escaping or other interpretation. Most users should instead choose the
-- 'setQueryString' function, which takes a parameter mapping.
-- | Sets the request's query string to be the raw bytestring provided,
-- without any escaping or other interpretation. Most users should instead
-- choose the 'setQueryString' function, which takes a parameter mapping.
setQueryStringRaw :: Monad m => ByteString -> RequestBuilder m ()
setQueryStringRaw r = do
rq <- rGet
Expand Down Expand Up @@ -408,8 +410,8 @@ setHttpVersion v = rModify $ \rq -> rq { rqVersion = v }

------------------------------------------------------------------------------
-- | Sets the request's path. The path provided must begin with a \"@/@\" and
-- must /not/ contain a query string; if you want to provide a query string in
-- your test request, you must use 'setQueryString' or 'setQueryStringRaw'.
-- must /not/ contain a query string; if you want to provide a query string
-- in your test request, you must use 'setQueryString' or 'setQueryStringRaw'.
-- Note that 'rqContextPath' is never set by any 'RequestBuilder' function.
setRequestPath :: Monad m => ByteString -> RequestBuilder m ()
setRequestPath p = do
Expand Down Expand Up @@ -499,11 +501,11 @@ postRaw uri contentType postData = do
-- defining a test request, runs the handler, producing an HTTP 'Response'.
runHandler' :: (MonadIO m, MonadSnap n) =>
(forall a . Request -> n a -> m Response)
-- ^ a function defining how the 'MonadSnap' monad should be run
-- ^ a function defining how the 'MonadSnap' monad should be run
-> RequestBuilder m ()
-- ^ a request builder
-- ^ a request builder
-> n b
-- ^ a web handler
-- ^ a web handler
-> m Response
runHandler' rSnap rBuilder snap = do
rq <- buildRequest rBuilder
Expand All @@ -513,8 +515,8 @@ runHandler' rSnap rBuilder snap = do


------------------------------------------------------------------------------
-- | Given a web handler in the 'Snap' monad, and a 'RequestBuilder' defining a
-- test request, runs the handler, producing an HTTP 'Response'.
-- | Given a web handler in the 'Snap' monad, and a 'RequestBuilder' defining
-- a test request, runs the handler, producing an HTTP 'Response'.
runHandler :: MonadIO m =>
RequestBuilder m () -- ^ a request builder
-> Snap a -- ^ a web handler
Expand Down
18 changes: 10 additions & 8 deletions src/Snap/Internal/Types.hs
Expand Up @@ -338,8 +338,8 @@ getRequestBody = liftM L.fromChunks $ runRequestBody consume
readRequestBody :: MonadSnap m =>
Int64 -- ^ size of the largest request body we're willing
-- to accept. If a request body longer than this is
-- received, a 'TooManyBytesReadException' is thrown.
-- See 'takeNoMoreThan'.
-- received, a 'TooManyBytesReadException' is
-- thrown. See 'takeNoMoreThan'.
-> m L.ByteString
readRequestBody sz = liftM L.fromChunks $ runRequestBody $
joinI $ takeNoMoreThan sz $$ consume
Expand Down Expand Up @@ -508,7 +508,7 @@ pathArg f = do
let (p,_) = S.break (=='/') (rqPathInfo req)
a <- fromBS p
localRequest (updateContextPath $ S.length p) (f a)


------------------------------------------------------------------------------
-- | Runs a 'Snap' monad action only when 'rqPathInfo' is empty.
Expand Down Expand Up @@ -824,7 +824,8 @@ instance Exception NoHandlerException


------------------------------------------------------------------------------
data ConnectionTerminatedException = ConnectionTerminatedException SomeException
data ConnectionTerminatedException =
ConnectionTerminatedException SomeException
deriving (Typeable)


Expand Down Expand Up @@ -937,15 +938,16 @@ readCookie name = maybe pass (fromBS . cookieValue) =<< getCookie name

------------------------------------------------------------------------------
-- | Expire the given 'Cookie' in client's browser.
expireCookie :: (MonadSnap m)
=> ByteString
expireCookie :: (MonadSnap m)
=> ByteString
-- ^ Cookie name
-> Maybe ByteString
-> Maybe ByteString
-- ^ Cookie domain
-> m ()
expireCookie nm dm = do
let old = UTCTime (ModifiedJulianDay 0) 0
modifyResponse $ addResponseCookie (Cookie nm "" (Just old) Nothing dm False False)
modifyResponse $ addResponseCookie
$ Cookie nm "" (Just old) Nothing dm False False


------------------------------------------------------------------------------
Expand Down
5 changes: 3 additions & 2 deletions src/Snap/Iteratee.hs
Expand Up @@ -684,10 +684,11 @@ enumBuilderToByteString :: MonadIO m => Enumeratee Builder ByteString m a
enumBuilderToByteString = builderToByteString

------------------------------------------------------------------------------
unsafeEnumBuilderToByteString :: MonadIO m => Enumeratee Builder ByteString m a
unsafeEnumBuilderToByteString :: MonadIO m
=> Enumeratee Builder ByteString m a
unsafeEnumBuilderToByteString =
builderToByteStringWith (reuseBufferStrategy (allocBuffer 65536))


------------------------------------------------------------------------------
enumByteStringToBuilder :: MonadIO m => Enumeratee ByteString Builder m a
Expand Down
4 changes: 2 additions & 2 deletions src/Snap/Test.hs
@@ -1,6 +1,6 @@
-- | The Snap.Test module contains primitives and combinators for testing Snap
-- applications.
module Snap.Test
module Snap.Test
( -- * Combinators and types for testing Snap handlers.

-- ** Types
Expand Down Expand Up @@ -52,4 +52,4 @@ module Snap.Test
import Snap.Internal.Test.Assertions
import Snap.Internal.Test.RequestBuilder


3 changes: 2 additions & 1 deletion src/Snap/Util/FileServe.hs
Expand Up @@ -265,7 +265,8 @@ snapIndexStyles =
, "border-top: 1px solid rgb(194,209,225);"
, "color: rgb(160,172,186); font-size:10pt;"
, "background: rgb(245,249,255) }"
, "table { max-width:100%; margin: 0 auto; border-collapse: collapse; }"
, "table { max-width:100%; margin: 0 auto;"++
" border-collapse: collapse; }"
, "tr:hover { background:rgb(256,256,224) }"
, "td { border:0; font-family:monospace; padding: 2px 0; }"
, "td.filename, td.type { padding-right: 2em; }"
Expand Down

0 comments on commit 4717e49

Please sign in to comment.