Package: discontinue support for GHC < 7.10.1

This commit is contained in:
Jonathan Daugherty 2017-01-22 11:05:06 -08:00
parent 745f1f6778
commit 700e759c32
18 changed files with 3 additions and 142 deletions

View File

@ -8,10 +8,9 @@ matrix:
- env: CABALVER=head GHCVER=head
env:
- CABALVER=1.20 GHCVER=7.6.3
- CABALVER=1.20 GHCVER=7.8.3
- CABALVER=1.22 GHCVER=7.10.1
- CABALVER=1.24 GHCVER=8.0.1
- CABALVER=1.24 GHCVER=8.0.2
- CABALVER=head GHCVER=head
install:

View File

@ -1,7 +1,8 @@
[![Build Status](https://travis-ci.org/jtdaugherty/vty.png)](https://travis-ci.org/jtdaugherty/vty)
`vty` is a terminal interface library. It provides a high-level
interface for doing terminal I/O.
interface for doing terminal I/O. Vty is supported on GHC versions
7.10.1 and up.
Install via `git` with:

View File

@ -1,13 +1,8 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK hide #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Evaluates the paramaterized terminfo string capability with the
-- given parameters.
module Data.Terminfo.Eval
@ -28,10 +23,6 @@ import Data.List
import qualified Data.Vector.Unboxed as Vector
#if !(MIN_VERSION_base(4,8,0))
import Data.Word
#endif
-- | capability evaluator state
data EvalState = EvalState
{ evalStack :: ![CapParam]

View File

@ -1,14 +1,9 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# OPTIONS_GHC -funbox-strict-fields -O #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Data.Terminfo.Parse
( module Data.Terminfo.Parse
, Text.Parsec.ParseError
@ -25,10 +20,6 @@ import Numeric (showHex)
import Text.Parsec
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
data CapExpression = CapExpression
{ capOps :: !CapOps
, capBytes :: !(Vector.Vector Word8)

View File

@ -1,12 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Display attributes
--
-- Typically the values 'defAttr' or 'currentAttr' are modified to form
@ -47,10 +42,6 @@ import Data.Word
import Graphics.Vty.Attributes.Color
import Graphics.Vty.Attributes.Color240
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
-- | A display attribute defines the Color and Style of all the
-- characters rendered after the attribute is applied.
--

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
@ -80,11 +79,7 @@ module Graphics.Vty.Config
)
where
#if __GLASGOW_HASKELL__ > 704
import Prelude
#else
import Prelude hiding (catch)
#endif
import Control.Applicative hiding (many)
@ -115,9 +110,7 @@ data VtyConfigurationError
deriving (Show, Eq, Typeable)
instance Exception VtyConfigurationError where
#if MIN_VERSION_base(4,8,0)
displayException VtyMissingTermEnvVar = "TERM environment variable not set"
#endif
-- | Mappings from input bytes to event in the order specified. Later
-- entries take precedence over earlier in the case multiple entries

View File

@ -1,21 +1,12 @@
-- Copyright 2009-2010 Corey O'Connor
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.DisplayAttributes where
import Graphics.Vty.Attributes
import Data.Bits ((.&.))
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (Monoid(..), mconcat)
#endif
-- | Given the previously applied display attributes as a FixedAttr and
-- the current display attributes as an Attr produces a FixedAttr that
-- represents the current display attributes. This is done by using the

View File

@ -1,12 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE DeriveGeneric #-}
{-# OPTIONS_HADDOCK hide #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.Image.Internal where
import Graphics.Vty.Attributes
@ -18,10 +13,6 @@ import Control.DeepSeq
import qualified Data.Text.Lazy as TL
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
-- | A display text is a Data.Text.Lazy
type DisplayText = TL.Text

View File

@ -1,10 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | The inline module provides a limited interface to changing the
-- style of terminal output. The intention is for this interface to be
-- used inline with other output systems.
@ -53,11 +48,6 @@ import Data.IORef
import System.IO
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
import Data.Monoid ( mappend )
#endif
type InlineM v = State Attr v
-- | Set the background color to the provided 'Color'

View File

@ -1,16 +1,10 @@
{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK hide #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.Inline.Unsafe where
import Graphics.Vty
import Data.Default
import Data.Monoid
import Data.IORef
import GHC.IO.Handle (hDuplicate)
@ -21,10 +15,6 @@ import System.IO.Unsafe
import System.Posix.IO (handleToFd)
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
#endif
globalVty :: IORef (Maybe Vty)
{-# NOINLINE globalVty #-}
globalVty = unsafePerformIO $ newIORef Nothing

View File

@ -1,10 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | The input layer for VTY. This provides methods for initializing an
-- 'Input' structure which can then be used to read 'Event's from the
-- terminal.
@ -163,12 +158,7 @@ import Lens.Micro
import qualified System.Console.Terminfo as Terminfo
import System.Posix.Signals.Exts
#if !(MIN_VERSION_base(4,8,0))
import Data.Functor ((<$>))
import Data.Monoid
#else
import Data.Monoid ((<>))
#endif
-- | Set up the terminal with file descriptor `inputFd` for input.
-- Returns a 'Input'.

View File

@ -24,7 +24,6 @@ import Control.Applicative
import Control.Concurrent
import Control.Concurrent.STM
import Control.Exception (mask, try, SomeException)
import Data.Monoid
import Lens.Micro
import Lens.Micro.Mtl
import Lens.Micro.TH

View File

@ -1,16 +1,11 @@
-- Copyright Corey O'Connor
-- General philosophy is: MonadIO is for equations exposed to clients.
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.Output.Interface
( Output(..)
, AssumedState(..)
@ -42,10 +37,6 @@ import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Vector as Vector
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mempty, mappend)
#endif
-- | Modal terminal features that can be enabled and disabled.
data Mode = Mouse
| BracketedPaste

View File

@ -1,13 +1,8 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -D_XOPEN_SOURCE=500 -fno-warn-warnings-deprecations #-}
{-# CFILES gwinsz.c #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Terminfo based terminal handling.
--
-- The color handling assumes tektronix like. No HP support provided. If
@ -47,11 +42,6 @@ import qualified System.Console.Terminfo as Terminfo
import System.Posix.IO (fdWriteBuf)
import System.Posix.Types (Fd(..))
#if !(MIN_VERSION_base(4,8,0))
import Data.Foldable (foldMap)
import Data.Monoid
#endif
data TerminfoCaps = TerminfoCaps
{ smcup :: Maybe CapExpression
, rmcup :: Maybe CapExpression

View File

@ -1,9 +1,3 @@
{-# LANGUAGE CPP #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- Copyright 2009-2010 Corey O'Connor
module Graphics.Vty.Output.XTermColor
( reserveTerminal
@ -25,11 +19,6 @@ import System.Posix.IO (fdWrite)
import System.Posix.Types (Fd)
import System.Posix.Env (getEnv)
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
import Data.Foldable (foldMap)
#endif
import Data.List (isInfixOf)
import Data.Maybe (catMaybes)
import Data.Monoid ((<>))

View File

@ -1,15 +1,10 @@
-- Copyright Corey O'Connor<coreyoconnor@gmail.com>
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Transforms an image into rows of operations.
module Graphics.Vty.PictureToSpans where
@ -24,12 +19,7 @@ import Lens.Micro.Mtl
import Lens.Micro.TH
import Control.Monad.Reader
import Control.Monad.State.Strict hiding ( state )
#if __GLASGOW_HASKELL__ < 708
import Control.Monad.ST.Strict hiding ( unsafeIOToST )
#else
import Control.Monad.ST.Strict
#endif
import qualified Data.Vector as Vector hiding ( take, replicate )
import Data.Vector.Mutable ( MVector(..))
@ -37,10 +27,6 @@ import qualified Data.Vector.Mutable as MVector
import qualified Data.Text.Lazy as TL
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mappend)
#endif
type MRowOps s = MVector s SpanOps
type MSpanOps s = MVector s SpanOp

View File

@ -1,7 +1,6 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
@ -86,15 +85,5 @@ instance Arbitrary DoubleColumnChar where
liftIOResult :: Testable prop => IO prop -> Property
liftIOResult = ioProperty
#if __GLASGOW_HASKELL__ <= 701
instance Random Word where
random g =
let (i :: Int, g') = random g
in (toEnum i, g')
randomR (l,h) g =
let (i :: Int, g') = randomR (fromEnum l,fromEnum h) g
in (toEnum i, g')
#endif
data Bench where
Bench :: forall v . NFData v => IO v -> (v -> IO ()) -> Bench

View File

@ -11,7 +11,6 @@ import Graphics.Vty.Input.Events
import Graphics.Vty.Input.Loop
import Graphics.Vty.Input.Terminfo
import Control.Applicative
import Control.Concurrent
import Control.Concurrent.STM
import Control.Exception