Merge pull request #1534 from yesodweb/reduce-deps

Reduce deps
This commit is contained in:
Michael Snoyman 2018-07-04 09:34:31 +03:00 committed by GitHub
commit ea182bb464
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
15 changed files with 10 additions and 112 deletions

View File

@ -16,9 +16,6 @@ import Yesod.Core.Types
import Control.Monad.Logger (MonadLogger)
import Control.Monad.Trans.Resource (MonadResource)
import Control.Monad.Trans.Class (lift)
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (Monoid)
#endif
import Data.Conduit.Internal (Pipe, ConduitM)
import Control.Monad.Trans.Identity ( IdentityT)

View File

@ -2,7 +2,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
module Yesod.Core.Class.Yesod where
import Yesod.Core.Content
@ -14,9 +13,6 @@ import Data.ByteString.Builder (Builder)
import Data.Text.Encoding (encodeUtf8Builder)
import Control.Arrow ((***), second)
import Control.Exception (bracket)
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
#endif
import Control.Monad (forM, when, void)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Logger (LogLevel (LevelInfo, LevelOther),

View File

@ -4,7 +4,6 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Yesod.Core.Content
( -- * Content
Content (..)
@ -56,9 +55,6 @@ import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8Builder)
import qualified Data.Text.Lazy as TL
import Data.ByteString.Builder (Builder, byteString, lazyByteString, stringUtf8)
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (mempty)
#endif
import Text.Hamlet (Html)
import Text.Blaze.Html.Renderer.Utf8 (renderHtmlBuilder)
import Data.Conduit (Flush (Chunk), SealedConduitT, mapOutput)

View File

@ -3,7 +3,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE CPP #-}
module Yesod.Core.Dispatch
( -- * Quasi-quoted routing
parseRoutes
@ -48,9 +47,6 @@ import qualified Network.Wai as W
import Data.ByteString.Lazy.Char8 ()
import Data.Text (Text)
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (mappend)
#endif
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Char8 as S8
@ -61,7 +57,7 @@ import Yesod.Core.Types
import Yesod.Core.Class.Yesod
import Yesod.Core.Class.Dispatch
import Yesod.Core.Internal.Run
import Safe (readMay)
import Text.Read (readMaybe)
import System.Environment (getEnvironment)
import qualified System.Random as Random
import Control.AutoUpdate (mkAutoUpdate, defaultUpdateSettings, updateAction, updateFreq)
@ -243,7 +239,7 @@ warpEnv site = do
case lookup "PORT" env of
Nothing -> error "warpEnv: no PORT environment variable found"
Just portS ->
case readMay portS of
case readMaybe portS of
Nothing -> error $ "warpEnv: invalid PORT environment variable: " ++ show portS
Just port -> warp port site

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
@ -195,10 +194,6 @@ import Yesod.Core.Internal.Request (langKey, mkFileInfoFile,
mkFileInfoLBS, mkFileInfoSource)
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
import Data.Monoid (mempty, mappend)
#endif
import Control.Applicative ((<|>))
import qualified Data.CaseInsensitive as CI
import Control.Exception (evaluate, SomeException, throwIO)
@ -249,7 +244,6 @@ import Yesod.Core.Class.Handler
import Yesod.Core.Types
import Yesod.Routes.Class (Route)
import Data.ByteString.Builder (Builder)
import Safe (headMay)
import Data.CaseInsensitive (CI, original)
import qualified Data.Conduit.List as CL
import Control.Monad.Trans.Resource (MonadResource, InternalState, runResourceT, withInternalState, getInternalState, liftResourceT, resourceForkIO)
@ -606,7 +600,7 @@ setMessageI = addMessageI ""
-- | Gets just the last message in the user's session,
-- discards the rest and the status
getMessage :: MonadHandler m => m (Maybe Html)
getMessage = fmap (fmap snd . headMay) getMessages
getMessage = fmap (fmap snd . listToMaybe) getMessages
-- | Bypass remaining handler code and output the given file.
--
@ -1322,7 +1316,7 @@ selectRep w = do
tryAccept ct =
if subType == "*"
then if mainType == "*"
then headMay reps
then listToMaybe reps
else Map.lookup mainType mainTypeMap
else lookupAccept ct
where

View File

@ -1,9 +1,6 @@
{-# LANGUAGE TypeFamilies, PatternGuards, CPP #-}
module Yesod.Core.Internal.LiteApp where
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid
#endif
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup (Semigroup(..))
#endif

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RankNTypes #-}
@ -9,10 +8,6 @@
module Yesod.Core.Internal.Run where
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (Monoid, mempty)
import Control.Applicative ((<$>))
#endif
import Yesod.Core.Internal.Response
import Data.ByteString.Builder (toLazyByteString)
import qualified Data.ByteString.Lazy as BL
@ -287,10 +282,8 @@ runFakeHandler fakeSessionMap logger site handler = liftIO $ do
, vault = mempty
, requestBodyLength = KnownLength 0
, requestHeaderRange = Nothing
#if MIN_VERSION_wai(3,2,0)
, requestHeaderReferer = Nothing
, requestHeaderUserAgent = Nothing
#endif
}
fakeRequest =
YesodRequest

View File

@ -3,7 +3,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
module Yesod.Core.Internal.TH where
@ -17,9 +16,6 @@ import qualified Network.Wai as W
import Data.ByteString.Lazy.Char8 ()
import Data.List (foldl')
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
#endif
import Control.Monad (replicateM, void)
import Text.Parsec (parse, many1, many, eof, try, option, sepBy1)
import Text.ParserCombinators.Parsec.Char (alphaNum, spaces, string, char)
@ -126,11 +122,7 @@ mkYesodGeneral :: [[String]] -- ^ Appliction context. Used in Ren
-> Q([Dec],[Dec])
mkYesodGeneral appCxt' namestr mtys isSub f resS = do
let appCxt = fmap (\(c:rest) ->
#if MIN_VERSION_template_haskell(2,10,0)
foldl' (\acc v -> acc `AppT` nameToType v) (ConT $ mkName c) rest
#else
ClassP (mkName c) $ fmap nameToType rest
#endif
) appCxt'
mname <- lookupTypeName namestr
arity <- case mname of
@ -140,13 +132,8 @@ mkYesodGeneral appCxt' namestr mtys isSub f resS = do
case info of
TyConI dec ->
case dec of
#if MIN_VERSION_template_haskell(2,11,0)
DataD _ _ vs _ _ _ -> length vs
NewtypeD _ _ vs _ _ _ -> length vs
#else
DataD _ _ vs _ _ -> length vs
NewtypeD _ _ vs _ _ -> length vs
#endif
TySynD _ vs _ -> length vs
_ -> 0
_ -> 0
@ -230,8 +217,4 @@ mkYesodSubDispatch res = do
return $ LetE [fun] (VarE helper)
instanceD :: Cxt -> Type -> [Dec] -> Dec
#if MIN_VERSION_template_haskell(2,11,0)
instanceD = InstanceD Nothing
#else
instanceD = InstanceD
#endif

View File

@ -11,11 +11,6 @@
module Yesod.Core.Types where
import qualified Data.ByteString.Builder as BB
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative (Applicative (..))
import Control.Applicative ((<$>))
import Data.Monoid (Monoid (..))
#endif
import Control.Arrow (first)
import Control.Exception (Exception)
import Control.Monad (ap)
@ -57,7 +52,6 @@ import Yesod.Core.Internal.Util (getTime, putTime)
import Yesod.Routes.Class (RenderRoute (..), ParseRoute (..))
import Control.Monad.Reader (MonadReader (..))
import Control.DeepSeq (NFData (rnf))
import Control.DeepSeq.Generics (genericRnf)
import Yesod.Core.TypeCache (TypeMap, KeyedTypeMap)
import Control.Monad.Logger (MonadLoggerIO (..))
import UnliftIO (MonadUnliftIO (..), UnliftIO (..))
@ -323,8 +317,7 @@ data ErrorResponse =
| PermissionDenied !Text
| BadMethod !H.Method
deriving (Show, Eq, Typeable, Generic)
instance NFData ErrorResponse where
rnf = genericRnf
instance NFData ErrorResponse
----- header stuff
-- | Headers to be added to a 'Result'.

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
-- | This is designed to be used as
--
-- > import qualified Yesod.Core.Unsafe as Unsafe
@ -10,9 +9,6 @@ import Yesod.Core.Internal.Run (runFakeHandler)
import Yesod.Core.Types
import Yesod.Core.Class.Yesod
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (mempty, mappend)
#endif
import Control.Monad.IO.Class (MonadIO)
-- | designed to be used as

View File

@ -8,7 +8,6 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
-- | Widgets combine HTML with JS and CSS dependencies with a unique identifier
-- generator, allowing you to create truly modular HTML components.
module Yesod.Core.Widget
@ -57,9 +56,6 @@ import Text.Cassius
import Text.Julius
import Yesod.Routes.Class
import Yesod.Core.Handler (getMessageRender, getUrlRenderParams)
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
#endif
import Text.Shakespeare.I18N (RenderMessage)
import Data.Text (Text)
import qualified Data.Map as Map

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
module Yesod.Routes.TH.ParseRoute
( -- ** ParseRoute
@ -45,8 +44,4 @@ mkParseRouteInstance cxt typ ress = do
fixDispatch x = x
instanceD :: Cxt -> Type -> [Dec] -> Dec
#if MIN_VERSION_template_haskell(2,11,0)
instanceD = InstanceD Nothing
#else
instanceD = InstanceD
#endif

View File

@ -7,22 +7,14 @@ module Yesod.Routes.TH.RenderRoute
) where
import Yesod.Routes.TH.Types
#if MIN_VERSION_template_haskell(2,11,0)
import Language.Haskell.TH (conT)
#endif
import Language.Haskell.TH.Syntax
#if MIN_VERSION_template_haskell(2,11,0)
import Data.Bits (xor)
#endif
import Data.Maybe (maybeToList)
import Control.Monad (replicateM)
import Data.Text (pack)
import Web.PathPieces (PathPiece (..), PathMultiPiece (..))
import Yesod.Routes.Class
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
import Data.Monoid (mconcat)
#endif
-- | Generate the constructors of a route data type.
mkRouteCons :: [ResourceTree Type] -> Q ([Con], [Dec])
@ -50,10 +42,8 @@ mkRouteCons rttypes =
(cons, decs) <- mkRouteCons children
#if MIN_VERSION_template_haskell(2,12,0)
dec <- DataD [] (mkName name) [] Nothing cons <$> fmap (pure . DerivClause Nothing) (mapM conT [''Show, ''Read, ''Eq])
#elif MIN_VERSION_template_haskell(2,11,0)
dec <- DataD [] (mkName name) [] Nothing cons <$> mapM conT [''Show, ''Read, ''Eq]
#else
let dec = DataD [] (mkName name) [] cons [''Show, ''Read, ''Eq]
dec <- DataD [] (mkName name) [] Nothing cons <$> mapM conT [''Show, ''Read, ''Eq]
#endif
return ([con], dec : decs)
where
@ -154,12 +144,9 @@ mkRenderRouteInstance cxt typ ress = do
#if MIN_VERSION_template_haskell(2,12,0)
did <- DataInstD [] ''Route [typ] Nothing cons <$> fmap (pure . DerivClause Nothing) (mapM conT (clazzes False))
let sds = fmap (\t -> StandaloneDerivD Nothing cxt $ ConT t `AppT` ( ConT ''Route `AppT` typ)) (clazzes True)
#elif MIN_VERSION_template_haskell(2,11,0)
#else
did <- DataInstD [] ''Route [typ] Nothing cons <$> mapM conT (clazzes False)
let sds = fmap (\t -> StandaloneDerivD cxt $ ConT t `AppT` ( ConT ''Route `AppT` typ)) (clazzes True)
#else
let did = DataInstD [] ''Route [typ] cons clazzes'
let sds = []
#endif
return $ instanceD cxt (ConT ''RenderRoute `AppT` typ)
[ did
@ -167,25 +154,14 @@ mkRenderRouteInstance cxt typ ress = do
]
: sds ++ decs
where
#if MIN_VERSION_template_haskell(2,11,0)
clazzes standalone = if standalone `xor` null cxt then
clazzes'
else
[]
#endif
clazzes' = [''Show, ''Eq, ''Read]
#if MIN_VERSION_template_haskell(2,11,0)
notStrict :: Bang
notStrict = Bang NoSourceUnpackedness NoSourceStrictness
#else
notStrict :: Strict
notStrict = NotStrict
#endif
instanceD :: Cxt -> Type -> [Dec] -> Dec
#if MIN_VERSION_template_haskell(2,11,0)
instanceD = InstanceD Nothing
#else
instanceD = InstanceD
#endif

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
module Yesod.Routes.TH.RouteAttrs
@ -10,9 +9,6 @@ import Yesod.Routes.Class
import Language.Haskell.TH.Syntax
import Data.Set (fromList)
import Data.Text (pack)
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
#endif
mkRouteAttrsInstance :: Cxt -> Type -> [ResourceTree a] -> Q Dec
mkRouteAttrsInstance cxt typ ress = do
@ -42,8 +38,4 @@ goRes front Resource {..} =
toText s = VarE 'pack `AppE` LitE (StringL s)
instanceD :: Cxt -> Type -> [Dec] -> Dec
#if MIN_VERSION_template_haskell(2,11,0)
instanceD = InstanceD Nothing
#else
instanceD = InstanceD
#endif

View File

@ -36,7 +36,6 @@ library
, containers >= 0.2
, cookie >= 0.4.3 && < 0.5
, deepseq >= 1.3
, deepseq-generics
, fast-logger >= 2.2
, http-types >= 0.7
, monad-logger >= 0.3.10 && < 0.4
@ -45,10 +44,9 @@ library
, path-pieces >= 0.1.2 && < 0.3
, random >= 1.0.0.2 && < 1.2
, resourcet >= 1.2
, safe
, semigroups
, rio
, shakespeare >= 2.0
, template-haskell
, template-haskell >= 2.11
, text >= 0.7
, time >= 1.5
, transformers >= 0.4
@ -56,7 +54,7 @@ library
, unliftio
, unordered-containers >= 0.2
, vector >= 0.9 && < 0.13
, wai >= 3.0
, wai >= 3.2
, wai-extra >= 3.0.7
, wai-logger >= 0.2
, warp >= 3.0.2