diff --git a/Hack/Middleware/CleanPath.hs b/Hack/Middleware/CleanPath.hs index 71c6973e..0fc1d82c 100644 --- a/Hack/Middleware/CleanPath.hs +++ b/Hack/Middleware/CleanPath.hs @@ -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 diff --git a/Hack/Middleware/ClientSession.hs b/Hack/Middleware/ClientSession.hs index 76a9f8cb..963fffe2 100644 --- a/Hack/Middleware/ClientSession.hs +++ b/Hack/Middleware/ClientSession.hs @@ -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' } diff --git a/Yesod.hs b/Yesod.hs index 6d492102..124c83d4 100644 --- a/Yesod.hs +++ b/Yesod.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE TemplateHaskell #-} --------------------------------------------------------- -- -- Module : Yesod diff --git a/Yesod/Handler.hs b/Yesod/Handler.hs index 50d2ff16..4b997079 100644 --- a/Yesod/Handler.hs +++ b/Yesod/Handler.hs @@ -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 diff --git a/Yesod/Helpers/Auth.hs b/Yesod/Helpers/Auth.hs index 96229ce6..e443ab18 100644 --- a/Yesod/Helpers/Auth.hs +++ b/Yesod/Helpers/Auth.hs @@ -37,7 +37,6 @@ import Control.Monad.Reader import Control.Monad.Attempt import Data.Maybe (fromMaybe) -import Control.Monad.Attempt data AuthResource = Check diff --git a/Yesod/Rep.hs b/Yesod/Rep.hs index ae5e4998..02952ca6 100644 --- a/Yesod/Rep.hs +++ b/Yesod/Rep.hs @@ -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" diff --git a/Yesod/Request.hs b/Yesod/Request.hs index 515f0388..e8263a74 100644 --- a/Yesod/Request.hs +++ b/Yesod/Request.hs @@ -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