hlint cleanup

This commit is contained in:
Michael Snoyman 2009-12-14 23:48:39 +02:00
parent 12437533b6
commit 603ebb3672
7 changed files with 10 additions and 10 deletions

View File

@ -33,7 +33,7 @@ splitPath :: String -> Either String [String]
splitPath s =
let corrected = ats $ rds s
in if corrected == s
then Right $ map decodeUrl $ filter (\l -> length l /= 0)
then Right $ map decodeUrl $ filter (not . null)
$ splitOneOf "/" s
else Left corrected

View File

@ -76,7 +76,7 @@ clientsession cnames key app env = do
twentyMinutes = 20 * 60
let exp = fromIntegral twentyMinutes `addUTCTime` now
let formattedExp = formatTime defaultTimeLocale "%a, %d-%b-%Y %X %Z" exp
let oldCookies = filter (\(k, _) -> not $ k `elem` map fst interceptHeaders) convertedCookies
let oldCookies = filter (\(k, _) -> k `notElem` map fst interceptHeaders) convertedCookies
let newCookies = map (setCookie key exp formattedExp remoteHost') $
oldCookies ++ interceptHeaders
let res' = res { headers = newCookies ++ headers' }

View File

@ -1,4 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
---------------------------------------------------------
--
-- Module : Yesod

View File

@ -65,8 +65,8 @@ instance Monad (Handler yesod) where
(headers, c) <- handler rr
(headers', c') <-
case c of
(HCError e) -> return $ ([], HCError e)
(HCSpecial e) -> return $ ([], HCSpecial e)
(HCError e) -> return ([], HCError e)
(HCSpecial e) -> return ([], HCSpecial e)
(HCContent a) -> unHandler (f a) rr
return (headers ++ headers', c')
instance MonadIO (Handler yesod) where

View File

@ -37,7 +37,6 @@ import Control.Monad.Reader
import Control.Monad.Attempt
import Data.Maybe (fromMaybe)
import Control.Monad.Attempt
data AuthResource =
Check

View File

@ -44,7 +44,8 @@ module Yesod.Rep
import Data.ByteString.Lazy (ByteString)
import Data.Text.Lazy (Text)
import Data.Maybe (catMaybes)
import Data.Maybe (mapMaybe)
import Data.Function (on)
#if TEST
import Data.Object.Html hiding (testSuite)
@ -93,7 +94,7 @@ instance Show ContentType where
show TypeOctet = "application/octet-stream"
show (TypeOther s) = s
instance Eq ContentType where
x == y = show x == show y
(==) = (==) `on` show
newtype Content = Content { unContent :: ByteString }
deriving (Eq, Show)
@ -115,7 +116,7 @@ class HasReps a where
chooseRep :: a -> RepChooser
chooseRep a ts = do
let (ct, c) =
case catMaybes $ map helper ts of
case mapMaybe helper ts of
(x:_) -> x
[] -> case reps of
[] -> error "Empty reps"

View File

@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverlappingInstances #-} -- Parameter String
{-# LANGUAGE TypeSynonymInstances #-}
---------------------------------------------------------
--
-- Module : Yesod.Request
@ -274,7 +275,7 @@ instance Parameter a => Parameter [a] where
Left l -> Left l
Right rest' -> Right $ r : rest'
instance Parameter [Char] where
instance Parameter String where
readParam = Right . paramValue
instance Parameter Int where