Skip to content

Commit

Permalink
deleted: drop GHC 7 test
Browse files Browse the repository at this point in the history
Yesod drop support GHC 7.
[yesod/.travis.yml at cdba6c1678d8002eac94ba175e00183a7e87c09d ·
yesodweb/yesod](https://github.com/yesodweb/yesod/blob/cdba6c1678d8002eac94ba175e00183a7e87c09d/.travis.yml)

GHC 7 is slow, and GHC 7 support add CPP switch.
To drop GHC 7 get correct travis test and simple code.

I delete unneed CPP pragma.

I rename `pattern` to `newPattern` because it cause hlint error.
  • Loading branch information
ncaq committed Sep 8, 2018
1 parent ed6dd85 commit dfd6f92
Show file tree
Hide file tree
Showing 14 changed files with 12 additions and 157 deletions.
43 changes: 0 additions & 43 deletions .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -35,24 +35,6 @@ matrix:
include:
# We grab the appropriate GHC and cabal-install versions from hvr's PPA. See:
# https://github.com/hvr/multi-ghc-travis
#- env: BUILD=cabal GHCVER=7.0.4 CABALVER=1.16 HAPPYVER=1.19.5 ALEXVER=3.1.7
# compiler: ": #GHC 7.0.4"
# addons: {apt: {packages: [cabal-install-1.16,ghc-7.0.4,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
#- env: BUILD=cabal GHCVER=7.2.2 CABALVER=1.16 HAPPYVER=1.19.5 ALEXVER=3.1.7
# compiler: ": #GHC 7.2.2"
# addons: {apt: {packages: [cabal-install-1.16,ghc-7.2.2,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
#- env: BUILD=cabal GHCVER=7.4.2 CABALVER=1.16 HAPPYVER=1.19.5 ALEXVER=3.1.7
# compiler: ": #GHC 7.4.2"
# addons: {apt: {packages: [cabal-install-1.16,ghc-7.4.2,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
- env: BUILD=cabal GHCVER=7.6.3 CABALVER=1.16 HAPPYVER=1.19.5 ALEXVER=3.1.7
compiler: ": #GHC 7.6.3"
addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.3,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
- env: BUILD=cabal GHCVER=7.8.4 CABALVER=1.18 HAPPYVER=1.19.5 ALEXVER=3.1.7
compiler: ": #GHC 7.8.4"
addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.4,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
- env: BUILD=cabal GHCVER=7.10.3 CABALVER=1.22 HAPPYVER=1.19.5 ALEXVER=3.1.7
compiler: ": #GHC 7.10.3"
addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
- env: BUILD=cabal GHCVER=8.0.2 CABALVER=1.24 HAPPYVER=1.19.5 ALEXVER=3.1.7
compiler: ": #GHC 8.0.2"
addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.2,happy-1.19.5,alex-3.1.7], sources: [hvr-ghc]}}
Expand All @@ -69,18 +51,6 @@ matrix:
compiler: ": #stack default"
addons: {apt: {packages: [libgmp-dev]}}

- env: BUILD=stack ARGS="--resolver lts-2"
compiler: ": #stack 7.8.4"
addons: {apt: {packages: [libgmp-dev]}}

- env: BUILD=stack ARGS="--resolver lts-3"
compiler: ": #stack 7.10.2"
addons: {apt: {packages: [libgmp-dev]}}

- env: BUILD=stack ARGS="--resolver lts-6"
compiler: ": #stack 7.10.3"
addons: {apt: {packages: [libgmp-dev]}}

- env: BUILD=stack ARGS="--resolver lts-7"
compiler: ": #stack 8.0.1"
addons: {apt: {packages: [libgmp-dev]}}
Expand All @@ -99,19 +69,6 @@ matrix:
compiler: ": #stack default osx"
os: osx

# Travis includes an macOS which is incompatible with GHC 7.8.4
#- env: BUILD=stack ARGS="--resolver lts-2"
# compiler: ": #stack 7.8.4 osx"
# os: osx

- env: BUILD=stack ARGS="--resolver lts-3"
compiler: ": #stack 7.10.2 osx"
os: osx

- env: BUILD=stack ARGS="--resolver lts-6"
compiler: ": #stack 7.10.3 osx"
os: osx

- env: BUILD=stack ARGS="--resolver lts-7"
compiler: ": #stack 8.0.1 osx"
os: osx
Expand Down
4 changes: 0 additions & 4 deletions Text/Cassius.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
module Text.Cassius
( -- * Datatypes
Expand Down Expand Up @@ -56,9 +55,6 @@ cassius = QuasiQuoter { quoteExp = quoteExp lucius . i2b }

cassiusFile :: FilePath -> Q Exp
cassiusFile fp = do
#ifdef GHC_7_4
qAddDependentFile fp
#endif
contents <- fmap TL.unpack $ qRunIO $ readUtf8File fp
quoteExp cassius contents

Expand Down
17 changes: 2 additions & 15 deletions Text/Hamlet.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
Expand Down Expand Up @@ -50,11 +49,7 @@ module Text.Hamlet

import Text.Shakespeare.Base
import Text.Hamlet.Parse
#if MIN_VERSION_template_haskell(2,9,0)
import Language.Haskell.TH.Syntax hiding (Module)
#else
import Language.Haskell.TH.Syntax
#endif
import Language.Haskell.TH.Quote
import Data.Char (isUpper, isDigit)
import Data.Maybe (fromMaybe)
Expand Down Expand Up @@ -122,8 +117,8 @@ unIdent (Ident s) = s
bindingPattern :: Binding -> Q (Pat, [(Ident, Exp)])
bindingPattern (BindAs i@(Ident s) b) = do
name <- newName s
(pattern, scope) <- bindingPattern b
return (AsP name pattern, (i, VarE name):scope)
(newPattern, scope) <- bindingPattern b
return (AsP name newPattern, (i, VarE name):scope)
bindingPattern (BindVar i@(Ident s))
| s == "_" = return (WildP, [])
| all isDigit s = do
Expand Down Expand Up @@ -183,13 +178,8 @@ recordToFieldNames conStr = do
-- use 'lookupValueName' instead of just using 'mkName' so we reify the
-- data constructor and not the type constructor if their names match.
Just conName <- lookupValueName $ conToStr conStr
#if MIN_VERSION_template_haskell(2,11,0)
DataConI _ _ typeName <- reify conName
TyConI (DataD _ _ _ _ cons _) <- reify typeName
#else
DataConI _ _ typeName _ <- reify conName
TyConI (DataD _ _ _ cons _) <- reify typeName
#endif
[fields] <- return [fields | RecC name fields <- cons, name == conName]
return [fieldName | (fieldName, _, _) <- fields]

Expand Down Expand Up @@ -423,9 +413,6 @@ docFromString set s =

hamletFileWithSettings :: Q HamletRules -> HamletSettings -> FilePath -> Q Exp
hamletFileWithSettings qhr set fp = do
#ifdef GHC_7_4
qAddDependentFile fp
#endif
contents <- fmap TL.unpack $ qRunIO $ readUtf8File fp
hamletFromString qhr set contents

Expand Down
1 change: 0 additions & 1 deletion Text/Hamlet/Parse.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
module Text.Hamlet.Parse
( Result (..)
Expand Down
25 changes: 1 addition & 24 deletions Text/Hamlet/RT.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
Expand All @@ -24,20 +23,11 @@ import Control.Exception (Exception)
import Data.Typeable (Typeable)
import Text.Hamlet.Parse
import Data.List (intercalate)
#if MIN_VERSION_blaze_html(0,5,0)
import Text.Blaze.Html (Html)
import Text.Blaze.Internal (preEscapedString, preEscapedText)
#else
import Text.Blaze (preEscapedString, preEscapedText, Html)
#endif
import Data.Text (Text)

#if MIN_VERSION_exceptions(0,4,0)
import Control.Monad.Catch (MonadThrow, throwM)
#else
import Control.Monad.Catch (MonadCatch, throwM)
#define MonadThrow MonadCatch
#endif

type HamletMap url = [([String], HamletData url)]
type UrlRenderer url = (url -> [(Text, Text)] -> Text)
Expand Down Expand Up @@ -131,11 +121,7 @@ renderHamletRT :: MonadThrow m
-> m Html
renderHamletRT = renderHamletRT' False

#if MIN_VERSION_exceptions(0,4,0)
renderHamletRT' :: MonadThrow m
#else
renderHamletRT' :: MonadCatch m
#endif
=> Bool -- ^ should embeded template (via ^{..}) be plain Html or actual templates?
-> HamletRT
-> HamletMap url
Expand Down Expand Up @@ -192,12 +178,7 @@ renderHamletRT' tempAsHtml (HamletRT docs) scope0 renderUrl =
renderHamletRT' tempAsHtml (HamletRT docs') scope renderUrl
HDBool False -> go scope (SDCond cs els)
_ -> fa $ showName b ++ ": expected HDBool"
#if MIN_VERSION_exceptions(0,4,0)
lookup' :: MonadThrow m
#else
lookup' :: MonadCatch m
#endif
=> [String] -> [String] -> HamletMap url -> m (HamletData url)
lookup' :: MonadThrow m => [String] -> [String] -> HamletMap url -> m (HamletData url)
lookup' orig k m =
case lookup k m of
Nothing | k == ["True"] -> return $ HDBool True
Expand All @@ -210,11 +191,7 @@ fa = throwM . HamletRenderException
showName :: [String] -> String
showName = intercalate "." . reverse

#if MIN_VERSION_exceptions(0,4,0)
flattenDeref' :: MonadThrow f => Doc -> Deref -> f [String]
#else
flattenDeref' :: MonadCatch f => Doc -> Deref -> f [String]
#endif
flattenDeref' orig deref =
case flattenDeref deref of
Nothing -> throwM $ HamletUnsupportedDocException orig
Expand Down
7 changes: 0 additions & 7 deletions Text/Internal/Css.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE EmptyDataDecls #-}
module Text.Internal.Css where
Expand Down Expand Up @@ -71,9 +70,6 @@ instance Semigroup Mixin where
Mixin a x <> Mixin b y = Mixin (a ++ b) (x ++ y)
instance Monoid Mixin where
mempty = Mixin mempty mempty
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif

data TopLevel a where
TopBlock :: !(Block a) -> TopLevel a
Expand Down Expand Up @@ -108,9 +104,6 @@ data CDData url = CDPlain Builder

pack :: String -> Text
pack = T.pack
#if !MIN_VERSION_text(0, 11, 2)
{-# NOINLINE pack #-}
#endif

fromText :: Text -> Builder
fromText = TLB.fromText
Expand Down
1 change: 0 additions & 1 deletion Text/Internal/CssCommon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
module Text.Internal.CssCommon where

import Text.Internal.Css
Expand Down
4 changes: 0 additions & 4 deletions Text/Lucius.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
module Text.Lucius
Expand Down Expand Up @@ -223,9 +222,6 @@ parseComment = do

luciusFile :: FilePath -> Q Exp
luciusFile fp = do
#ifdef GHC_7_4
qAddDependentFile fp
#endif
contents <- fmap TL.unpack $ qRunIO $ readUtf8File fp
luciusFromString contents

Expand Down
15 changes: 2 additions & 13 deletions Text/MkSizeType.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
-- | Internal functions to generate CSS size wrapper types.
module Text.MkSizeType (mkSizeType) where

#if MIN_VERSION_template_haskell(2,11,0)
#if !MIN_VERSION_template_haskell(2,12,0)
import Language.Haskell.TH (conT)
#endif
import Language.Haskell.TH.Syntax
Expand All @@ -25,10 +25,8 @@ dataDec name =
#if MIN_VERSION_template_haskell(2,12,0)
return $
DataD [] name [] Nothing [constructor] [DerivClause Nothing (map ConT derives)]
#elif MIN_VERSION_template_haskell(2,11,0)
DataD [] name [] Nothing [constructor] <$> mapM conT derives
#else
return $ DataD [] name [] [constructor] derives
DataD [] name [] Nothing [constructor] <$> mapM conT derives
#endif
where constructor = NormalC name [(notStrict, ConT $ mkName "Rational")]
derives = map mkName ["Eq", "Ord"]
Expand Down Expand Up @@ -88,17 +86,8 @@ unariFunDec2 name fun' = FunD fun [Clause [pat] body []]
fun = mkName fun'
x = mkName "x"

#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
20 changes: 3 additions & 17 deletions Text/Shakespeare.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,11 +41,10 @@ import Text.Parsec.Prim (modifyState, Parsec)
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH (appE)
import Language.Haskell.TH.Syntax
#if !MIN_VERSION_template_haskell(2,8,0)
import Language.Haskell.TH.Syntax.Internals
#endif
import Data.Text.Lazy.Builder (Builder, fromText)
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid
#endif
import System.IO.Unsafe (unsafePerformIO)
import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL
Expand All @@ -63,12 +62,6 @@ import Data.Data (Data)
import System.Process (readProcessWithExitCode)
import System.Exit (ExitCode(..))

#if !MIN_VERSION_base(4,5,0)
(<>) :: Monoid m => m -> m -> m
(<>) = mappend
{-# INLINE (<>) #-}
#endif

-- | A parser with a user state of [String]
type Parser = Parsec String [String]
-- | run a parser with a user state of [String]
Expand Down Expand Up @@ -344,9 +337,6 @@ preFilter mfp ShakespeareSettings {..} template =

pack' :: String -> TS.Text
pack' = TS.pack
#if !MIN_VERSION_text(0, 11, 2)
{-# NOINLINE pack' #-}
#endif

contentsToShakespeare :: ShakespeareSettings -> [Content] -> Q Exp
contentsToShakespeare rs a = do
Expand Down Expand Up @@ -394,11 +384,7 @@ shakespeareFromString r str = do
contentsToShakespeare r $ contentFromString r s

shakespeareFile :: ShakespeareSettings -> FilePath -> Q Exp
shakespeareFile r fp =
#ifdef GHC_7_4
qAddDependentFile fp >>
#endif
readFileQ fp >>= shakespeareFromString r
shakespeareFile r fp = readFileQ fp >>= shakespeareFromString r

data VarType = VTPlain | VTUrl | VTUrlParam | VTMixin
deriving (Show, Eq, Ord, Enum, Bounded, Typeable, Data, Generic)
Expand Down
19 changes: 1 addition & 18 deletions Text/Shakespeare/I18N.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE CPP #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -156,9 +155,6 @@ mkMessageCommon genType prefix postfix master dt folder lang = do
files <- qRunIO $ getDirectoryContents folder
let files' = filter (`notElem` [".", ".."]) files
(_files', contents) <- qRunIO $ fmap (unzip . catMaybes) $ mapM (loadLang folder) files'
#ifdef GHC_7_4
mapM_ qAddDependentFile $ concat _files'
#endif
let contents' = Map.toList $ Map.fromListWith (++) contents
sdef <-
case lookup lang contents' of
Expand All @@ -171,11 +167,7 @@ mkMessageCommon genType prefix postfix master dt folder lang = do
c3 <- defClause
return $
( if genType
then ((DataD [] mname []
#if MIN_VERSION_template_haskell(2,11,0)
Nothing
#endif
(map (toCon dt) sdef) []) :)
then ((DataD [] mname [] Nothing (map (toCon dt) sdef) []) :)
else id)
[ instanceD
[]
Expand Down Expand Up @@ -407,17 +399,8 @@ instance IsString (SomeMessage master) where
instance master ~ master' => RenderMessage master (SomeMessage master') where
renderMessage a b (SomeMessage msg) = renderMessage a b msg

#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
Loading

0 comments on commit dfd6f92

Please sign in to comment.