API: remove dependency on data-default

This change removes Data.Default instances for Attr and Config. Use
'defAttr' and 'defaultConfig' (or 'mempty') instead of 'def'.
This commit is contained in:
Jonathan Daugherty 2017-01-22 12:00:55 -08:00
parent e621e59b7a
commit 9809a42189
7 changed files with 19 additions and 34 deletions

View File

@ -36,7 +36,6 @@ module Graphics.Vty.Attributes
where
import Data.Bits
import Data.Default
import Data.Word
import Graphics.Vty.Attributes.Color
@ -211,9 +210,6 @@ withStyle attr styleFlag = attr { attrStyle = SetTo $ styleMask attr .|. styleFl
defAttr :: Attr
defAttr = Attr Default Default Default
instance Default Attr where
def = defAttr
-- | Keeps the style, background color and foreground color that was
-- previously set. Used to override some part of the previous style.
--

View File

@ -76,6 +76,7 @@ module Graphics.Vty.Config
, standardIOConfig
, runParseConfig
, parseConfigFile
, defaultConfig
)
where
@ -87,7 +88,6 @@ import Control.Exception (catch, IOException, Exception(..), throwIO)
import Control.Monad (liftM, guard, void)
import qualified Data.ByteString as BS
import Data.Default
import Data.Monoid
import Data.Typeable (Typeable)
@ -146,8 +146,8 @@ data Config = Config
, termName :: Maybe String
} deriving (Show, Eq)
instance Default Config where
def = mempty
defaultConfig :: Config
defaultConfig = mempty
instance Monoid Config where
mempty = Config
@ -179,14 +179,14 @@ instance Monoid Config where
userConfig :: IO Config
userConfig = do
configFile <- (mappend <$> getAppUserDataDirectory "vty" <*> pure "/config") >>= parseConfigFile
overrideConfig <- maybe (return def) parseConfigFile =<< getEnv "VTY_CONFIG_FILE"
overrideConfig <- maybe (return defaultConfig) parseConfigFile =<< getEnv "VTY_CONFIG_FILE"
let base = configFile <> overrideConfig
mappend base <$> overrideEnvConfig
overrideEnvConfig :: IO Config
overrideEnvConfig = do
d <- getEnv "VTY_DEBUG_LOG"
return $ def { debugLog = d }
return $ defaultConfig { debugLog = d }
-- | Configures VTY using defaults suitable for terminals. This action
-- can raise 'VtyConfigurationError'.
@ -196,7 +196,7 @@ standardIOConfig = do
case mb of
Nothing -> throwIO VtyMissingTermEnvVar
Just t ->
return def
return defaultConfig
{ vmin = Just 1
, mouseMode = Just False
, bracketedPasteMode = Just False
@ -209,13 +209,13 @@ standardIOConfig = do
parseConfigFile :: FilePath -> IO Config
parseConfigFile path = do
catch (runParseConfig path <$> BS.readFile path)
(\(_ :: IOException) -> return def)
(\(_ :: IOException) -> return defaultConfig)
runParseConfig :: String -> BS.ByteString -> Config
runParseConfig name cfgTxt =
case runParser parseConfig () name cfgTxt of
Right cfg -> cfg
Left{} -> def
Left{} -> defaultConfig
------------------------------------------------------------------------
@ -249,13 +249,13 @@ mapDecl = do
bytes <- P.stringLiteral configLexer
key <- parseValue
modifiers <- parseValue
return def { inputMap = [(termIdent, bytes, EvKey key modifiers)] }
return defaultConfig { inputMap = [(termIdent, bytes, EvKey key modifiers)] }
debugLogDecl :: Parser Config
debugLogDecl = do
"debugLog" <- P.identifier configLexer
path <- P.stringLiteral configLexer
return def { debugLog = Just path }
return defaultConfig { debugLog = Just path }
ignoreLine :: Parser ()
ignoreLine = void $ manyTill anyChar newline
@ -264,7 +264,7 @@ parseConfig :: Parser Config
parseConfig = liftM mconcat $ many $ do
P.whiteSpace configLexer
let directives = [try mapDecl, try debugLogDecl]
choice directives <|> (ignoreLine >> return def)
choice directives <|> (ignoreLine >> return defaultConfig)
class Parse a where parseValue :: Parser a
instance Parse Char where parseValue = P.charLiteral configLexer

View File

@ -4,7 +4,6 @@ module Graphics.Vty.Inline.Unsafe where
import Graphics.Vty
import Data.Default
import Data.IORef
import GHC.IO.Handle (hDuplicate)
@ -29,7 +28,7 @@ mkDupeConfig = do
hSetBuffering stdin NoBuffering
stdinDupe <- hDuplicate stdin >>= handleToFd
stdoutDupe <- hDuplicate stdout >>= handleToFd
return $ def { inputFd = Just stdinDupe, outputFd = Just stdoutDupe }
return $ defaultConfig { inputFd = Just stdinDupe, outputFd = Just stdoutDupe }
-- | This will create a Vty instance using 'mkVty' and execute an IO
-- action provided that instance. The created Vty instance will be

View File

@ -4,7 +4,6 @@ module Main where
import Graphics.Vty.Config
import Graphics.Vty.Input.Events
import Data.Default
import Data.String.QQ
import qualified Data.ByteString.Char8 as B
@ -24,7 +23,7 @@ debugLog "/tmp/vty-debug.txt"
|]
exampleConfigConfig :: Config
exampleConfigConfig = def
exampleConfigConfig = defaultConfig
{ debugLog = Just "/tmp/vty-debug.txt"
, inputMap = [ (Nothing, "\ESC[B", EvKey KUp [])
, (Nothing, "\ESC[1;3B", EvKey KDown [MAlt])

View File

@ -12,8 +12,6 @@ import Verify.Graphics.Vty.Output
import Control.Monad
import Data.Default
import qualified System.Console.Terminfo as Terminfo
import System.Posix.Env
import System.Posix.IO
@ -37,7 +35,7 @@ smokeTestTermNonMac termName i = liftIOResult $ do
smokeTestTerm :: String -> Image -> IO Result
smokeTestTerm termName i = do
nullOut <- openFd "/dev/null" WriteOnly Nothing defaultFileFlags
t <- outputForConfig $ def { outputFd = Just nullOut, termName = Just termName }
t <- outputForConfig $ defaultConfig { outputFd = Just nullOut, termName = Just termName }
-- putStrLn $ "context color count: " ++ show (contextColorCount t)
reserveDisplay t
dc <- displayContext t (100,100)

View File

@ -17,7 +17,6 @@ import Control.Exception
import Lens.Micro ((^.))
import Control.Monad
import Data.Default
import Data.IORef
import Data.List (intersperse, reverse, nubBy)
@ -113,11 +112,11 @@ assertEventsFromSynInput table inputSpec expectedEvents = do
(writeFd, readFd) <- openPseudoTerminal
(setTermAttr,_) <- attributeControl readFd
setTermAttr
let testConfig = def { inputFd = Just readFd
, termName = Just "dummy"
, vmin = Just 1
, vtime = Just 100
}
let testConfig = defaultConfig { inputFd = Just readFd
, termName = Just "dummy"
, vmin = Just 1
, vtime = Just 100
}
input <- initInput testConfig table
eventsRef <- newIORef []
let writeWaitClose = do

View File

@ -43,7 +43,6 @@ library
blaze-builder >= 0.3.3.2 && < 0.5,
bytestring,
containers,
data-default >= 0.5.3,
deepseq >= 1.1 && < 1.5,
directory,
filepath >= 1.0 && < 2.0,
@ -129,7 +128,6 @@ executable vty-mode-demo
build-depends: vty,
base >= 4.6 && < 5,
containers,
data-default >= 0.5.3,
microlens,
microlens-mtl,
mtl >= 1.1.1.0 && < 2.3
@ -145,7 +143,6 @@ executable vty-demo
build-depends: vty,
base >= 4.6 && < 5,
containers,
data-default >= 0.5.3,
microlens,
microlens-mtl,
mtl >= 1.1.1.0 && < 2.3
@ -228,7 +225,6 @@ test-suite verify-terminal
base >= 4.6 && < 5,
bytestring,
containers,
data-default >= 0.5.3,
deepseq >= 1.1 && < 1.5,
mtl >= 1.1.1.0 && < 2.3,
terminfo >= 0.3 && < 0.5,
@ -569,7 +565,6 @@ test-suite verify-using-mock-input
build-depends: vty,
Cabal >= 1.20,
data-default >= 0.5.3,
QuickCheck >= 2.7,
smallcheck == 1.*,
quickcheck-assertions >= 0.1.1,
@ -604,7 +599,6 @@ test-suite verify-config
build-depends: vty,
Cabal >= 1.20,
data-default >= 0.5.3,
HUnit,
QuickCheck >= 2.7,
smallcheck == 1.*,