Update for Vty 5.15

This commit is contained in:
Jonathan Daugherty 2017-01-24 13:48:45 -08:00
parent 07059168d4
commit 4a2b90eae7
16 changed files with 62 additions and 77 deletions

View File

@ -78,9 +78,8 @@ library
Brick.Widgets.Internal
build-depends: base <= 5,
vty >= 5.12,
vty >= 5.15,
transformers,
data-default,
dlist,
containers,
microlens >= 0.3.0.0,
@ -103,7 +102,7 @@ executable brick-cache-demo
main-is: CacheDemo.hs
build-depends: base,
brick,
vty >= 5.12,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
microlens-th
@ -117,8 +116,7 @@ executable brick-visibility-demo
main-is: VisibilityDemo.hs
build-depends: base,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
microlens-th
@ -133,8 +131,7 @@ executable brick-viewport-scroll-demo
main-is: ViewportScrollDemo.hs
build-depends: base,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -147,8 +144,7 @@ executable brick-dialog-demo
main-is: DialogDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -161,8 +157,7 @@ executable brick-mouse-demo
main-is: MouseDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
microlens-th,
@ -177,8 +172,7 @@ executable brick-layer-demo
main-is: LayerDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
microlens-th
@ -192,8 +186,7 @@ executable brick-suspend-resume-demo
main-is: SuspendAndResumeDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
microlens-th
@ -207,8 +200,7 @@ executable brick-padding-demo
main-is: PaddingDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -221,8 +213,7 @@ executable brick-attr-demo
main-is: AttrDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -235,8 +226,7 @@ executable brick-markup-demo
main-is: MarkupDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -249,8 +239,7 @@ executable brick-list-demo
main-is: ListDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
vector
@ -264,8 +253,7 @@ executable brick-custom-event-demo
main-is: CustomEventDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens >= 0.3.0.0,
microlens-th
@ -279,8 +267,7 @@ executable brick-hello-world-demo
main-is: HelloWorldDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -293,8 +280,7 @@ executable brick-edit-demo
main-is: EditDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
vector,
microlens >= 0.3.0.0,
@ -310,8 +296,7 @@ executable brick-border-demo
main-is: BorderDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens
@ -325,7 +310,6 @@ executable brick-progressbar-demo
main-is: ProgressBarDemo.hs
build-depends: base <= 5,
brick,
vty >= 5.12,
data-default,
vty >= 5.15,
text,
microlens

View File

@ -343,7 +343,9 @@ our events over that channel. Once we've created the channel with
main :: IO ()
main = do
eventChan <- Control.Concurrent.newChan
finalState <- customMain (Graphics.Vty.mkVty Data.Default.def) (Just eventChan) app initialState
finalState <- customMain
(Graphics.Vty.mkVty Graphics.Vty.defaultConfig)
(Just eventChan) app initialState
-- Use finalState and exit
The ``customMain`` function lets us have control over how the ``vty``

View File

@ -6,7 +6,6 @@ import Lens.Micro ((^.), (&), (.~), (%~))
import Lens.Micro.TH (makeLenses)
import Control.Monad (void, forever)
import Control.Concurrent (newChan, writeChan, threadDelay, forkIO)
import Data.Default
import Data.Monoid
import qualified Graphics.Vty as V
@ -17,6 +16,9 @@ import Brick.Main
, continue
, halt
)
import Brick.AttrMap
( attrMap
)
import Brick.Types
( Widget
, Next
@ -65,7 +67,7 @@ theApp =
, appChooseCursor = showFirstCursor
, appHandleEvent = appEvent
, appStartEvent = return
, appAttrMap = def
, appAttrMap = const $ attrMap V.defAttr []
}
main :: IO ()
@ -76,4 +78,4 @@ main = do
writeChan chan Counter
threadDelay 1000000
void $ customMain (V.mkVty def) (Just chan) theApp initialState
void $ customMain (V.mkVty V.defaultConfig) (Just chan) theApp initialState

View File

@ -5,7 +5,6 @@ module Main where
import Lens.Micro ((^.), (&), (%~))
import Lens.Micro.TH (makeLenses)
import Control.Monad (void)
import Data.Default
import qualified Graphics.Vty as V
import qualified Brick.Types as T
@ -17,6 +16,9 @@ import Brick.Widgets.Core
( translateBy
, str
)
import Brick.AttrMap
( attrMap
)
data St =
St { _topLayerLocation :: T.Location
@ -70,7 +72,7 @@ app =
M.App { M.appDraw = drawUi
, M.appStartEvent = return
, M.appHandleEvent = appEvent
, M.appAttrMap = const def
, M.appAttrMap = const $ attrMap V.defAttr []
, M.appChooseCursor = M.neverShowCursor
}

View File

@ -1,8 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Data.Default
import Brick.Main (App(..), neverShowCursor, resizeOrQuit, defaultMain)
import Brick.Types
( Widget
@ -22,6 +20,8 @@ import Brick.Widgets.Core
)
import Brick.Widgets.Border as B
import Brick.Widgets.Center as C
import Brick.AttrMap (attrMap)
import qualified Graphics.Vty as V
ui :: Widget ()
ui =
@ -50,7 +50,7 @@ app =
App { appDraw = const [ui]
, appHandleEvent = resizeOrQuit
, appStartEvent = return
, appAttrMap = const def
, appAttrMap = const $ attrMap V.defAttr []
, appChooseCursor = neverShowCursor
}

View File

@ -6,13 +6,15 @@ import Lens.Micro ((.~), (^.), (&))
import Lens.Micro.TH (makeLenses)
import Control.Monad (void)
import Data.Monoid
import Data.Default
import qualified Graphics.Vty as V
import Brick.Main
( App(..), neverShowCursor, defaultMain
, suspendAndResume, halt, continue
)
import Brick.AttrMap
( attrMap
)
import Brick.Types
( Widget
, EventM
@ -59,7 +61,7 @@ theApp =
, appChooseCursor = neverShowCursor
, appHandleEvent = appEvent
, appStartEvent = return
, appAttrMap = const def
, appAttrMap = const $ attrMap V.defAttr []
}
main :: IO ()

View File

@ -7,7 +7,6 @@ import Control.Applicative
import Control.Monad (void)
import Data.Monoid ((<>))
import Data.Default
import qualified Graphics.Vty as V
import qualified Brick.Types as T
@ -18,6 +17,9 @@ import Brick.Types
( Widget
, ViewportType(Horizontal, Vertical, Both)
)
import Brick.AttrMap
( attrMap
)
import Brick.Widgets.Core
( hLimit
, vLimit
@ -75,7 +77,7 @@ app =
M.App { M.appDraw = drawUi
, M.appStartEvent = return
, M.appHandleEvent = appEvent
, M.appAttrMap = const def
, M.appAttrMap = const $ attrMap V.defAttr []
, M.appChooseCursor = M.neverShowCursor
}

View File

@ -49,7 +49,6 @@ import qualified Data.Map as M
import Data.Maybe (catMaybes)
import Data.List (inits)
import Data.String (IsString(..))
import Data.Default (Default(..))
import Graphics.Vty (Attr(..), MaybeDefault(..))
@ -68,9 +67,6 @@ import Graphics.Vty (Attr(..), MaybeDefault(..))
data AttrName = AttrName [String]
deriving (Show, Eq, Ord)
instance Default AttrName where
def = mempty
instance Monoid AttrName where
mempty = AttrName []
mappend (AttrName as) (AttrName bs) = AttrName $ as `mappend` bs
@ -83,9 +79,6 @@ data AttrMap = AttrMap Attr (M.Map AttrName Attr)
| ForceAttr Attr
deriving Show
instance Default AttrMap where
def = AttrMap def mempty
-- | Create an attribute name from a string.
attrName :: String -> AttrName
attrName = AttrName . (:[])

View File

@ -51,7 +51,6 @@ import Control.Concurrent (forkIO, Chan, newChan, readChan, writeChan, killThrea
import Control.Applicative ((<$>))
import Data.Monoid (mempty)
#endif
import Data.Default
import Data.Maybe (listToMaybe)
import qualified Data.Map as M
import qualified Data.Set as S
@ -66,7 +65,9 @@ import Graphics.Vty
, shutdown
, nextEvent
, mkVty
, defaultConfig
)
import Graphics.Vty.Attributes (defAttr)
import Brick.Types (Widget, EventM(..))
import Brick.Types.Internal
@ -119,7 +120,7 @@ defaultMain :: (Ord n)
-> IO s
defaultMain app st = do
chan <- newChan
customMain (mkVty def) (Just chan) app st
customMain (mkVty defaultConfig) (Just chan) app st
-- | A simple main entry point which takes a widget and renders it. This
-- event loop terminates when the user presses any key, but terminal
@ -132,7 +133,7 @@ simpleMain w =
let app = App { appDraw = const [w]
, appHandleEvent = resizeOrQuit
, appStartEvent = return
, appAttrMap = def
, appAttrMap = const $ attrMap defAttr []
, appChooseCursor = neverShowCursor
}
in defaultMain app ()

View File

@ -15,7 +15,6 @@ import Lens.Micro ((.~), (&), (^.))
import Control.Monad (forM)
import qualified Data.Text as T
import Data.Text.Markup
import Data.Default (def)
import Graphics.Vty (Attr, vertCat, horizCat, string)
@ -54,4 +53,4 @@ markup m =
return $ string a $ T.unpack t
return $ horizCat is
lineImgs <- mapM mkLine markupLines
return $ def & imageL .~ vertCat lineImgs
return $ emptyResult & imageL .~ vertCat lineImgs

View File

@ -43,6 +43,7 @@ module Brick.Types
-- ** Rendering results
, Result(..)
, emptyResult
, lookupAttrName
, Extent(..)

View File

@ -38,6 +38,7 @@ module Brick.Types.Internal
, cursorsL
, extentsL
, visibilityRequestsL
, emptyResult
)
where
@ -51,7 +52,6 @@ import Lens.Micro.Internal (Field1, Field2)
import qualified Data.Set as S
import qualified Data.Map as M
import Graphics.Vty (Vty, Event, Button, Modifier, DisplayRegion, Image, emptyImage)
import Data.Default (Default(..))
import Brick.Types.TH
import Brick.AttrMap (AttrName, AttrMap)
@ -194,8 +194,8 @@ data Result n =
suffixLenses ''Result
instance Default (Result n) where
def = Result emptyImage [] [] []
emptyResult :: Result n
emptyResult = Result emptyImage [] [] []
-- | The type of events.
data BrickEvent n e = VtyEvent Event

View File

@ -17,11 +17,10 @@ module Brick.Widgets.Border.Style
, unicode
, unicodeBold
, unicodeRounded
, defaultBorderStyle
)
where
import Data.Default
-- | A border style for use in any widget that needs to render borders
-- in a consistent style.
data BorderStyle =
@ -50,8 +49,8 @@ data BorderStyle =
}
deriving (Show, Read, Eq)
instance Default BorderStyle where
def = unicode
defaultBorderStyle :: BorderStyle
defaultBorderStyle = unicode
-- | Make a border style using the specified character everywhere.
borderStyleFromChar :: Char -> BorderStyle

View File

@ -92,7 +92,6 @@ import Control.Monad.Trans.Reader
import Control.Monad.Trans.Class (lift)
import qualified Data.Foldable as F
import qualified Data.Text as T
import Data.Default
import qualified Data.DList as DL
import qualified Data.Map as M
import qualified Data.Set as S
@ -207,13 +206,13 @@ str s =
fixEmpty l = l
dropUnused l = takeColumns (availWidth c) <$> take (availHeight c) l
case force theLines of
[] -> return def
[one] -> return $ def & imageL .~ (V.string (c^.attrL) one)
[] -> return emptyResult
[one] -> return $ emptyResult & imageL .~ (V.string (c^.attrL) one)
multiple ->
let maxLength = maximum $ V.safeWcswidth <$> multiple
lineImgs = lineImg <$> multiple
lineImg lStr = V.string (c^.attrL) (lStr ++ replicate (maxLength - V.safeWcswidth lStr) ' ')
in return $ def & imageL .~ (V.vertCat lineImgs)
in return $ emptyResult & imageL .~ (V.vertCat lineImgs)
-- | Build a widget from a one-line 'T.Text' value. Behaves the same as
-- 'str'.
@ -308,7 +307,7 @@ fill :: Char -> Widget n
fill ch =
Widget Greedy Greedy $ do
c <- getContext
return $ def & imageL .~ (V.charFill (c^.attrL) ch (c^.availWidthL) (c^.availHeightL))
return $ emptyResult & imageL .~ (V.charFill (c^.attrL) ch (c^.availWidthL) (c^.availHeightL))
-- | Vertical box layout: put the specified widgets one above the other
-- in the specified order (uppermost first). Defers growth policies to
@ -550,7 +549,7 @@ overrideAttr targetName fromName =
-- | Build a widget directly from a raw Vty image.
raw :: V.Image -> Widget n
raw img = Widget Fixed Fixed $ return $ def & imageL .~ img
raw img = Widget Fixed Fixed $ return $ emptyResult & imageL .~ img
-- | Translate the specified widget by the specified offset amount.
-- Defers to the translated widget for growth policy.

View File

@ -13,13 +13,13 @@ import Control.Applicative
import Lens.Micro ((^.), (&), (%~))
import Control.Monad.Trans.State.Lazy
import Control.Monad.Trans.Reader
import Data.Default
import Data.Maybe (catMaybes)
import qualified Graphics.Vty as V
import Brick.Types
import Brick.Types.Internal
import Brick.AttrMap
import Brick.Widgets.Border.Style
renderFinal :: AttrMap
-> [Widget n]
@ -32,7 +32,7 @@ renderFinal aMap layerRenders sz chooseCursor rs = (newRS, picWithBg, theCursor,
(layerResults, !newRS) = flip runState rs $ sequence $
(\p -> runReaderT p ctx) <$>
(render <$> cropToContext <$> layerRenders)
ctx = Context def (fst sz) (snd sz) def aMap
ctx = Context mempty (fst sz) (snd sz) defaultBorderStyle aMap
pic = V.picForLayers $ uncurry V.resize sz <$> (^.imageL) <$> layerResults
-- picWithBg is a workaround for runaway attributes.
-- See https://github.com/coreyoconnor/vty/issues/95

View File

@ -21,7 +21,6 @@ import Control.Applicative ((<$>))
import Data.Monoid
#endif
import Data.Default (Default, def)
import Data.String (IsString(..))
import qualified Data.Text as T
@ -34,7 +33,7 @@ instance Monoid (Markup a) where
mappend (Markup t1) (Markup t2) =
Markup (t1 `mappend` t2)
instance (Default a) => IsString (Markup a) where
instance (Monoid a) => IsString (Markup a) where
fromString = fromText . T.pack
-- | Build a piece of markup; assign the specified metadata to every
@ -43,8 +42,8 @@ instance (Default a) => IsString (Markup a) where
t @@ val = Markup [(c, val) | c <- T.unpack t]
-- | Build markup from text with the default metadata.
fromText :: (Default a) => T.Text -> Markup a
fromText = (@@ def)
fromText :: (Monoid a) => T.Text -> Markup a
fromText = (@@ mempty)
-- | Extract the text from markup, discarding the markup metadata.
toText :: (Eq a) => Markup a -> T.Text