Skip to content

Commit

Permalink
hlint
Browse files Browse the repository at this point in the history
  • Loading branch information
yihuang committed Dec 11, 2011
1 parent 10f5ad9 commit c2ecac6
Show file tree
Hide file tree
Showing 6 changed files with 23 additions and 24 deletions.
8 changes: 4 additions & 4 deletions Apps.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
module Apps where

import Control.Exception (fromException)
Expand Down Expand Up @@ -32,7 +32,7 @@ chatParser = ChatJoin <$> (string "join" *> skipSpace *> takeByteString)
<|> ChatData <$> takeByteString

instance UpProtocol ChatMessage where
decode s = parseOnly chatParser s
decode = parseOnly chatParser

instance DownProtocol ChatMessage where
encode (ChatData s) = s
Expand All @@ -48,7 +48,7 @@ chat :: ChatState -> WSLite ()
chat clients = do
name <- recvJoin
sink <- getSink
exists <- liftIO $ modifyMVar clients $ \cs -> do
exists <- liftIO $ modifyMVar clients $ \cs ->
case M.lookup name cs of
Nothing -> return (M.insert name sink cs, False)
Just _ -> return (cs, True)
Expand All @@ -71,7 +71,7 @@ chat clients = do

broadcast msg = do
sinks <- M.elems <$> liftIO (readMVar clients)
forM_ sinks (flip sendSink msg)
forM_ sinks (`sendSink` msg)

welcome name = do
users <- filter (/=name) . M.keys <$> liftIO (readMVar clients)
Expand Down
2 changes: 1 addition & 1 deletion Control/Concurrent/Timer.hs
Expand Up @@ -8,4 +8,4 @@ setTimeout :: Int -> IO () -> IO TimerId
setTimeout n ac = forkIO $ threadDelay n >> ac

clearTimeout :: TimerId -> IO ()
clearTimeout t = killThread t
clearTimeout = killThread
6 changes: 3 additions & 3 deletions Data/Enumerator/Utils.hs
Expand Up @@ -48,7 +48,7 @@ readTChan' chan = (:) <$> readTChan chan <*> readRest chan
else (:) <$> readTChan ch <*> readRest ch

-- | fetch multiple (at least one) chunks from TChan at a time, and combine them into one.
enumStreamChanContents :: Show a => StreamChan a -> Enumerator [a] IO b
enumStreamChanContents :: StreamChan a -> Enumerator [a] IO b
enumStreamChanContents ch = checkContinue0 $ \loop f -> do
streams <- liftIO $ atomically $ readTChan' ch
let chunks = takeWhile isChunk streams
Expand All @@ -67,10 +67,10 @@ concatMapMaybe f = checkDone (continue . step) where
step k (Chunks xs) = loop k xs

loop k [] = continue (step k)
loop k (x:xs) = do
loop k (x:xs) =
case f x of
Nothing -> k EOF >>==
(`yield` (Chunks xs))
(`yield` Chunks xs)
Just fx -> k (Chunks fx) >>==
checkDoneEx (Chunks xs) (`loop` xs)

Expand Down
5 changes: 2 additions & 3 deletions Data/List/Utils.hs
@@ -1,9 +1,8 @@
module Data.List.Utils where

groupWith :: (a -> a -> Maybe a) -> [a] -> [a]
groupWith f [] = []
groupWith f (x:[]) = [x]
groupWith f (x1:x2:xs) =
case (f x1 x2) of
case f x1 x2 of
Just x -> groupWith f (x:xs)
Nothing -> x1 : groupWith f (x2:xs)
groupWith f xs = xs
4 changes: 2 additions & 2 deletions Main.hs
Expand Up @@ -15,8 +15,8 @@ import Apps (echo, chat, close', newChatState, ChatState, chat)

staticApp :: Application
staticApp = Static.staticApp Static.defaultFileServerSettings
-- { Static.ssFolder = Static.embeddedLookup $ Static.toEmbedded $(embedDir "static") }
{ Static.ssFolder = Static.fileSystemLookup "static" }
{ Static.ssFolder = Static.embeddedLookup $ Static.toEmbedded $(embedDir "static") }
-- { Static.ssFolder = Static.fileSystemLookup "static" }

mkApps :: ChatState -> WSLiteRoute
mkApps st = [ ( ["echo"], (echo, Nothing) )
Expand Down
22 changes: 11 additions & 11 deletions Network/Sockjs.hs
Expand Up @@ -43,19 +43,19 @@ data SockjsMessage = SockjsOpen

renderSockjs :: SockjsMessage -> Builder
renderSockjs msg = case msg of
SockjsOpen -> B.fromByteString "o"
SockjsOpen -> B.fromByteString "o"
SockjsHeartbeat -> B.fromByteString "h"
(SockjsData xs) -> mconcat $
[ B.fromByteString "a"
, (fromValue . toJSON $ xs)
]
(SockjsData xs) -> mconcat
[ B.fromByteString "a"
, fromValue . toJSON $ xs
]
(SockjsClose code reason) -> B.fromLazyByteString . L.fromChunks $
[ "c["
, S.pack (show code)
, ",\""
, reason
, "\"]"
]
[ "c["
, S.pack (show code)
, ",\""
, reason
, "\"]"
]

decodeValue :: (FromJSON a) => ByteString -> Maybe a
decodeValue s = case parse value s of
Expand Down

0 comments on commit c2ecac6

Please sign in to comment.