Merge pull request #81 from glguy/710-cleanup

Clean up warnings when compiling on 7.10
This commit is contained in:
Corey O'Connor 2015-08-08 13:59:49 -07:00
commit 50ab1162a8
13 changed files with 135 additions and 26 deletions

View File

@ -1,7 +1,13 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS_GHC -funbox-strict-fields #-} {-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK hide #-} {-# 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. {- Evaluates the paramaterized terminfo string capability with the given parameters.
- -
-} -}
@ -17,11 +23,14 @@ import Control.Monad.State.Strict
import Control.Monad.Writer import Control.Monad.Writer
import Data.Bits ((.|.), (.&.), xor) import Data.Bits ((.|.), (.&.), xor)
import Data.List import Data.List
import Data.Word
import qualified Data.Vector.Unboxed as Vector import qualified Data.Vector.Unboxed as Vector
#if !(MIN_VERSION_base(4,8,0))
import Data.Word
#endif
-- | capability evaluator state -- | capability evaluator state
data EvalState = EvalState data EvalState = EvalState
{ evalStack :: ![CapParam] { evalStack :: ![CapParam]

View File

@ -1,8 +1,14 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# OPTIONS_GHC -funbox-strict-fields -O #-} {-# 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 module Data.Terminfo.Parse ( module Data.Terminfo.Parse
, Text.Parsec.ParseError , Text.Parsec.ParseError
) )
@ -11,7 +17,6 @@ module Data.Terminfo.Parse ( module Data.Terminfo.Parse
import Control.Monad ( liftM ) import Control.Monad ( liftM )
import Control.DeepSeq import Control.DeepSeq
import Data.Monoid
import Data.Word import Data.Word
import qualified Data.Vector.Unboxed as Vector import qualified Data.Vector.Unboxed as Vector
@ -19,6 +24,10 @@ import Numeric (showHex)
import Text.Parsec import Text.Parsec
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
data CapExpression = CapExpression data CapExpression = CapExpression
{ capOps :: !CapOps { capOps :: !CapOps
, capBytes :: !(Vector.Vector Word8) , capBytes :: !(Vector.Vector Word8)

View File

@ -1,6 +1,12 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GADTs #-} {-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Display attributes -- | Display attributes
-- --
-- Typically the values 'defAttr' or 'currentAttr' are modified to form attributes: -- Typically the values 'defAttr' or 'currentAttr' are modified to form attributes:
@ -33,12 +39,15 @@ module Graphics.Vty.Attributes ( module Graphics.Vty.Attributes
import Data.Bits import Data.Bits
import Data.Default import Data.Default
import Data.Monoid
import Data.Word import Data.Word
import Graphics.Vty.Attributes.Color import Graphics.Vty.Attributes.Color
import Graphics.Vty.Attributes.Color240 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 -- | A display attribute defines the Color and Style of all the characters rendered after the
-- attribute is applied. -- attribute is applied.
-- --

View File

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

View File

@ -1,5 +1,11 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.Image.Internal where module Graphics.Vty.Image.Internal where
import Graphics.Vty.Attributes import Graphics.Vty.Attributes
@ -7,9 +13,12 @@ import Graphics.Text.Width
import Control.DeepSeq import Control.DeepSeq
import Data.Monoid
import qualified Data.Text.Lazy as TL 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 -- | A display text is a Data.Text.Lazy
-- --
-- TODO(corey): hm. there is an explicit equation for each type which goes to a lazy text. Each -- TODO(corey): hm. there is an explicit equation for each type which goes to a lazy text. Each

View File

@ -24,7 +24,13 @@
-- 'putAttrChange' -- 'putAttrChange'
-- --
-- Copyright 2009-2010 Corey O'Connor -- Copyright 2009-2010 Corey O'Connor
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.Inline ( module Graphics.Vty.Inline module Graphics.Vty.Inline ( module Graphics.Vty.Inline
, withVty , withVty
) )
@ -37,15 +43,18 @@ import Graphics.Vty.Output.Interface
import Blaze.ByteString.Builder (writeToByteString) import Blaze.ByteString.Builder (writeToByteString)
import Control.Applicative
import Control.Monad.State.Strict import Control.Monad.State.Strict
import Data.Bits ( (.&.), complement ) import Data.Bits ( (.&.), complement )
import Data.IORef import Data.IORef
import Data.Monoid ( mappend )
import System.IO import System.IO
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
import Data.Monoid ( mappend )
#endif
type InlineM v = State Attr v type InlineM v = State Attr v
-- | Set the background color to the provided 'Color' -- | Set the background color to the provided 'Color'

View File

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

View File

@ -1,4 +1,10 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-} {-# 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 -- | 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. -- then be used to read 'Event's from the terminal.
-- --
@ -133,12 +139,14 @@ import Graphics.Vty.Input.Terminfo
import Control.Concurrent import Control.Concurrent
import Control.Lens import Control.Lens
import Data.Functor ((<$>))
import Data.Monoid
import qualified System.Console.Terminfo as Terminfo import qualified System.Console.Terminfo as Terminfo
import System.Posix.Signals.Exts import System.Posix.Signals.Exts
#if !(MIN_VERSION_base(4,8,0))
import Data.Functor ((<$>))
import Data.Monoid
#endif
-- | Set up the terminal with file descriptor `inputFd` for input. Returns a 'Input'. -- | Set up the terminal with file descriptor `inputFd` for input. Returns a 'Input'.
-- --
-- The table used to determine the 'Events' to produce for the input bytes comes from -- The table used to determine the 'Events' to produce for the input bytes comes from

View File

@ -1,5 +1,11 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Output interface. -- | Output interface.
-- --
-- Access to the current terminal or a specific terminal device. -- Access to the current terminal or a specific terminal device.
@ -40,10 +46,11 @@ import Blaze.ByteString.Builder (writeToByteString)
import Control.Monad.Trans import Control.Monad.Trans
import Data.Monoid (mappend)
import Data.List (isPrefixOf) import Data.List (isPrefixOf)
import System.Posix.Env (getEnv) #if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mappend)
#endif
-- | Returns a `Output` for the terminal specified in `Config` -- | Returns a `Output` for the terminal specified in `Config`
-- --

View File

@ -1,10 +1,16 @@
-- Copyright Corey O'Connor -- Copyright Corey O'Connor
-- General philosophy is: MonadIO is for equations exposed to clients. -- General philosophy is: MonadIO is for equations exposed to clients.
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-} {-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
module Graphics.Vty.Output.Interface module Graphics.Vty.Output.Interface
where where
@ -23,15 +29,18 @@ import Control.Monad.Trans
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.IORef import Data.IORef
import Data.Monoid (mempty, mappend)
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
import qualified Data.Vector as Vector import qualified Data.Vector as Vector
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mempty, mappend)
#endif
data Output = Output data Output = Output
{ -- | Text identifier for the output device. Used for debugging. { -- | Text identifier for the output device. Used for debugging.
terminalID :: String terminalID :: String
, releaseTerminal :: MonadIO m => m () , releaseTerminal :: forall m. MonadIO m => m ()
-- | Clear the display and initialize the terminal to some initial display state. -- | Clear the display and initialize the terminal to some initial display state.
-- --
-- The expectation of a program is that the display starts in some initial state. -- The expectation of a program is that the display starts in some initial state.
@ -46,12 +55,12 @@ data Output = Output
-- --
-- - The previous state cannot be determined -- - The previous state cannot be determined
-- - When exclusive access to a display is released the display returns to the previous state. -- - When exclusive access to a display is released the display returns to the previous state.
, reserveDisplay :: MonadIO m => m () , reserveDisplay :: forall m. MonadIO m => m ()
-- | Return the display to the state before `reserveDisplay` -- | Return the display to the state before `reserveDisplay`
-- If no previous state then set the display state to the initial state. -- If no previous state then set the display state to the initial state.
, releaseDisplay :: MonadIO m => m () , releaseDisplay :: forall m. MonadIO m => m ()
-- | Returns the current display bounds. -- | Returns the current display bounds.
, displayBounds :: MonadIO m => m DisplayRegion , displayBounds :: forall m. MonadIO m => m DisplayRegion
-- | Output the byte string to the terminal device. -- | Output the byte string to the terminal device.
, outputByteBuffer :: BS.ByteString -> IO () , outputByteBuffer :: BS.ByteString -> IO ()
-- | Maximum number of colors supported by the context. -- | Maximum number of colors supported by the context.
@ -62,7 +71,7 @@ data Output = Output
-- | Acquire display access to the given region of the display. -- | Acquire display access to the given region of the display.
-- Currently all regions have the upper left corner of (0,0) and the lower right corner at -- Currently all regions have the upper left corner of (0,0) and the lower right corner at
-- (max displayWidth providedWidth, max displayHeight providedHeight) -- (max displayWidth providedWidth, max displayHeight providedHeight)
, mkDisplayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext , mkDisplayContext :: forall m. MonadIO m => Output -> DisplayRegion -> m DisplayContext
} }
displayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext displayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext

View File

@ -3,6 +3,11 @@
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -D_XOPEN_SOURCE=500 -fno-warn-warnings-deprecations #-} {-# OPTIONS_GHC -D_XOPEN_SOURCE=500 -fno-warn-warnings-deprecations #-}
{-# CFILES gwinsz.c #-} {-# CFILES gwinsz.c #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- | Terminfo based terminal handling. -- | Terminfo based terminal handling.
-- --
-- The color handling assumes tektronix like. No HP support provided. If the terminal is not one I -- The color handling assumes tektronix like. No HP support provided. If the terminal is not one I
@ -28,10 +33,8 @@ import Blaze.ByteString.Builder (Write, writeToByteString)
import Control.Monad.Trans import Control.Monad.Trans
import Data.Bits ((.&.)) import Data.Bits ((.&.))
import Data.Foldable (foldMap)
import Data.IORef import Data.IORef
import Data.Maybe (isJust, isNothing, fromJust) import Data.Maybe (isJust, isNothing, fromJust)
import Data.Monoid
import Data.Word import Data.Word
import Foreign.C.Types ( CInt(..), CLong(..) ) import Foreign.C.Types ( CInt(..), CLong(..) )
@ -42,6 +45,11 @@ import qualified System.Console.Terminfo as Terminfo
import System.Posix.IO (fdWriteBuf) import System.Posix.IO (fdWriteBuf)
import System.Posix.Types (Fd(..)) import System.Posix.Types (Fd(..))
#if !(MIN_VERSION_base(4,8,0))
import Data.Foldable (foldMap)
import Data.Monoid
#endif
data TerminfoCaps = TerminfoCaps data TerminfoCaps = TerminfoCaps
{ smcup :: Maybe CapExpression { smcup :: Maybe CapExpression
, rmcup :: Maybe CapExpression , rmcup :: Maybe CapExpression

View File

@ -1,3 +1,9 @@
{-# LANGUAGE CPP #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
-- Copyright 2009-2010 Corey O'Connor -- Copyright 2009-2010 Corey O'Connor
module Graphics.Vty.Output.XTermColor ( reserveTerminal ) module Graphics.Vty.Output.XTermColor ( reserveTerminal )
where where
@ -8,15 +14,17 @@ import qualified Graphics.Vty.Output.TerminfoBased as TerminfoBased
import Blaze.ByteString.Builder (writeToByteString) import Blaze.ByteString.Builder (writeToByteString)
import Blaze.ByteString.Builder.Word (writeWord8) import Blaze.ByteString.Builder.Word (writeWord8)
import Control.Applicative
import Control.Monad (void) import Control.Monad (void)
import Control.Monad.Trans import Control.Monad.Trans
import Data.Foldable (foldMap)
import System.Posix.IO (fdWrite) import System.Posix.IO (fdWrite)
import System.Posix.Types (Fd) import System.Posix.Types (Fd)
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
import Data.Foldable (foldMap)
#endif
-- | Initialize the display to UTF-8. -- | Initialize the display to UTF-8.
reserveTerminal :: ( Applicative m, MonadIO m ) => String -> Fd -> m Output reserveTerminal :: ( Applicative m, MonadIO m ) => String -> Fd -> m Output
reserveTerminal variant outFd = liftIO $ do reserveTerminal variant outFd = liftIO $ do

View File

@ -5,6 +5,11 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
#ifndef MIN_VERSION_base
#defined MIN_VERSION_base(x,y,z) 1
#endif
{- | Transforms an image into rows of operations. {- | Transforms an image into rows of operations.
-} -}
module Graphics.Vty.PictureToSpans where module Graphics.Vty.PictureToSpans where
@ -27,12 +32,15 @@ import Control.Monad.ST.Strict
#endif #endif
import qualified Data.Vector as Vector hiding ( take, replicate ) import qualified Data.Vector as Vector hiding ( take, replicate )
import Data.Monoid (mappend)
import Data.Vector.Mutable ( MVector(..)) import Data.Vector.Mutable ( MVector(..))
import qualified Data.Vector.Mutable as MVector import qualified Data.Vector.Mutable as MVector
import qualified Data.Text.Lazy as TL 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 MRowOps s = MVector s SpanOps
type MSpanOps s = MVector s SpanOp type MSpanOps s = MVector s SpanOp