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.

And I run stylish-haskell all source code for import field.
Because I want to detect unneed or duplicate import.
  • Loading branch information
ncaq committed Aug 30, 2018
1 parent ed6dd85 commit 5cf32e0
Show file tree
Hide file tree
Showing 16 changed files with 208 additions and 355 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
29 changes: 12 additions & 17 deletions Text/Cassius.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
module Text.Cassius
( -- * Datatypes
Expand Down Expand Up @@ -40,25 +38,22 @@ module Text.Cassius
, cassiusUsedIdentifiers
) where

import Text.Internal.Css
import Text.Shakespeare.Base
import Text.Shakespeare (VarType)
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax
import qualified Data.Text.Lazy as TL
import Text.Internal.CssCommon
import Text.Lucius (lucius)
import qualified Data.Text.Lazy as TL
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax
import Text.IndentToBrace (i2b)
import Text.Internal.Css
import Text.Internal.CssCommon
import Text.Lucius (lucius)
import qualified Text.Lucius
import Text.IndentToBrace (i2b)
import Text.Shakespeare (VarType)
import Text.Shakespeare.Base

cassius :: QuasiQuoter
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
63 changes: 24 additions & 39 deletions Text/Hamlet.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
module Text.Hamlet
( -- * Plain HTML
Expand Down Expand Up @@ -48,32 +47,26 @@ module Text.Hamlet
, hamletFromString
) where

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)
import Data.Text (Text, pack)
import qualified Data.Text.Lazy as TL
import Text.Blaze.Html (Html, toHtml)
import Text.Blaze.Internal (preEscapedText)
import qualified Data.Foldable as F
import Control.Monad (mplus)
import Data.Monoid (mempty, mappend, mconcat)
import Control.Arrow ((***))
import Data.List (intercalate)

import Data.IORef
import qualified Data.Map as M
import System.IO.Unsafe (unsafePerformIO)
import System.Directory (getModificationTime)
import Data.Time (UTCTime)
import Text.Blaze.Html (preEscapedToHtml)
import Control.Arrow ((***))
import Control.Monad (mplus)
import Data.Char (isDigit, isUpper)
import qualified Data.Foldable as F
import Data.IORef
import Data.List (intercalate)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Monoid (mappend, mconcat, mempty)
import Data.Text (Text, pack)
import qualified Data.Text.Lazy as TL
import Data.Time (UTCTime)
import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax hiding (Module)
import System.Directory (getModificationTime)
import System.IO.Unsafe (unsafePerformIO)
import Text.Blaze.Html (Html, toHtml, preEscapedToHtml)
import Text.Blaze.Internal (preEscapedText)
import Text.Hamlet.Parse
import Text.Shakespeare.Base

-- | Convert some value to a list of attribute pairs.
class ToAttributes a where
Expand Down Expand Up @@ -122,8 +115,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 +176,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 +411,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
29 changes: 14 additions & 15 deletions Text/Hamlet/Parse.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Hamlet.Parse
( Result (..)
, Content (..)
Expand All @@ -20,17 +19,17 @@ module Text.Hamlet.Parse
)
where

import Text.Shakespeare.Base
import Control.Applicative ((<$>), Applicative (..))
import Control.Monad
import Control.Arrow
import Data.Char (isUpper)
import Data.Data
import Text.ParserCombinators.Parsec hiding (Line)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Maybe (mapMaybe, fromMaybe, isNothing)
import Language.Haskell.TH.Syntax (Lift (..))
import Control.Applicative (Applicative (..), (<$>))
import Control.Arrow
import Control.Monad
import Data.Char (isUpper)
import Data.Data
import Data.Maybe (fromMaybe, isNothing, mapMaybe)
import Data.Set (Set)
import qualified Data.Set as Set
import Language.Haskell.TH.Syntax (Lift (..))
import Text.ParserCombinators.Parsec hiding (Line)
import Text.Shakespeare.Base

data Result v = Error String | Ok v
deriving (Show, Eq, Read, Data, Typeable)
Expand Down
54 changes: 15 additions & 39 deletions Text/Hamlet/RT.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- | Provides functionality for runtime Hamlet templates. Please use
-- "Text.Hamlet.Runtime" instead.
module Text.Hamlet.RT
Expand All @@ -17,27 +16,17 @@ module Text.Hamlet.RT
, SimpleDoc (..)
) where

import Text.Shakespeare.Base
import Data.Monoid (mconcat)
import Control.Monad (liftM, forM)
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
import Control.Exception (Exception)
import Control.Monad (forM, liftM)
import Control.Monad.Catch (MonadThrow, throwM)
import Data.List (intercalate)
import Data.Monoid (mconcat)
import Data.Text (Text)
import Data.Typeable (Typeable)
import Text.Blaze.Html (Html)
import Text.Blaze.Internal (preEscapedString, preEscapedText)
import Text.Hamlet.Parse
import Text.Shakespeare.Base

type HamletMap url = [([String], HamletData url)]
type UrlRenderer url = (url -> [(Text, Text)] -> Text)
Expand Down Expand Up @@ -131,11 +120,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 +177,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 +190,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
Loading

0 comments on commit 5cf32e0

Please sign in to comment.