{-# LANGUAGE ForeignFunctionInterface, BangPatterns #-} {-# CFILES gwinsz.c #-} module Graphics.Vty.Cursor ( move , setCursorInvis , setCursorVis , mvputch ) where import Graphics.Vty.Types import Graphics.Vty.ControlStrings import Graphics.Vty.Output ( chgatt ,tputchar ,putShow ) import Control.Monad ( when ) {- import Data.Bits ( (.|.), (.&.), shiftR ) import Data.Maybe ( maybe ) import Foreign.C.Types ( CLong ) import Foreign.Ptr ( Ptr ) import Foreign.Storable ( peekElemOff, peek ) import Foreign.Marshal.Array ( advancePtr ) import System.IO ( stdout, hFlush ) -} -- | Move the cursor to (x,y); sx is the current width of the screen. -- (this is a bit of a hack, forcing clients to cache that data) move :: Int -> Int -> Int -> TermState -> IO TermState move sx x y (TS ox oy at) = do movcsr y oy x ox sx return (TS x y at) -- | Put a (char,attr) at a given (x,y) cursor position; sx is the -- current width of the screen. (this is a bit of a hack, forcing -- clients to cache that data) mvputch :: Int -> Int -> Int -> Char -> Attr -> TermState -> IO TermState mvputch !sx !x !y !ch !att !(TS ox oy oat) = do movcsr y oy x ox sx when (att /= oat) $ chgatt att tputchar ch return (TS (x+1) y att) -- | Make the cursor invisible. setCursorInvis :: TermState -> IO TermState setCursorInvis ts = putStr civis >> return ts -- | Make the cursor visible. setCursorVis :: TermState -> IO TermState setCursorVis ts = putStr cvis >> return ts -- we always use absolute motion between lines to work around diffs movcsr :: Int -> Int -> Int -> Int -> Int -> IO () movcsr y oy x ox wid | y /= oy || ox == wid = putStr "\ESC[" >> putShow (y+1) >> putChar ';' >> putShow (x+1) >> putChar 'H' | x == ox = return () | x == (ox + 1) = putStr "\ESC[C" | x > ox = putStr "\ESC[" >> putShow (x - ox) >> putChar 'C' | otherwise = putStr "\ESC[" >> putShow (ox - x) >> putChar 'D' {-# INLINE movcsr #-}