
On Wed, Dec 3, 2008 at 7:57 PM, Corey O'Connor
Hello, For further development of the vty package I'm really only paying attention to the requirements that fall out of the Yi project. Are there any other projects that depend on the vty package?
In addition, the vty project has it's own wiki: http://trac.haskell.org/vty/ Right now there isn't much information there but it is a great place to send bug reports or enhancement requests if you have them.
I haven't been using it for anything real, but I was playing around with it in preparation for yet another project that hasn't taken off (and it never might). Anyway, it is a nice _low-level_ library, do you have any plans on building convenient things on top of it? Basic widgets such as dialogues and lists spring to mind... This is a rather pathetic list widget I came up with at the time: module Main where import Data.Maybe import Graphics.Vty import qualified Data.ByteString.Char8 as B options = [ "01 Foo", "02 Bar", "03 Baz", "04 Qux", "05 Quux", "06 Quuux", "07 Foo", "08 Bar", "09 Baz", "10 Qux", "11 Quux", "12 Quuux", "13 Foo", "14 Bar", "15 Baz", "16 Qux", "17 Quux", "18 Quuux", "19 Foo", "20 Bar", "21 Baz", "22 Qux", "23 Quux", "24 Quuux", "25 Foo", "26 Bar", "27 Baz", "28 Qux", "29 Quux", "30 Quuux", "31 Foo", "32 Bar", "33 Baz", "34 Qux", "35 Quux", "36 Quuux", "37 Foo", "38 Bar", "39 Baz", "40 Qux", "41 Quux", "42 Quuux", "43 Foo", "44 Bar", "45 Baz", "46 Qux", "47 Quux", "48 Quuux", "49 Foo", "50 Bar", "51 Baz", "52 Qux", "53 Quux", "54 Quuux", "55 Foo", "56 Bar", "57 Baz", "58 Qux", "59 Quux", "60 Quuux" ] main :: IO () main = do vt <- mkVty getChoice vt options >>= putStrLn . show {- - List choice widget for Vty. -} getChoice :: Vty -> [String] -> IO (Maybe (Int, String)) getChoice vt opts = do (sx, sy) <- getSize vt _getChoice vt opts 0 sx sy _getChoice vt opts idx sx sy = let _calcTop winHeight listLength idx = max 0 ((min listLength ((max 0 (idx - winHeight `div` 2)) + winHeight)) - winHeight) _top = _calcTop sy (length opts) idx _visible_opts = take sy (drop _top opts) in do update vt (render _visible_opts (idx - _top) sx) k <- getEvent vt case k of EvKey KDown [] -> _getChoice vt opts (min (length opts - 1) (idx + 1)) sx sy EvKey KUp [] -> _getChoice vt opts (max 0 (idx - 1)) sx sy EvKey KEsc [] -> shutdown vt >> return Nothing EvKey KEnter [] -> shutdown vt >> return (Just $ (idx, opts !! idx)) EvResize nx ny -> _getChoice vt opts idx nx ny _ -> _getChoice vt opts idx sx sy render opts idx sx = pic { pImage = foldr1 (<->) $ map _render1 $ zip [0..] opts } where _render1 (i, o) = renderHFill attr ' ' 5 <|> renderBS (_attr i) (B.pack o) <|> renderHFill attr ' ' (sx - 5 - length o) _attr i = if i /= idx then attr else setRV attr /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe