{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Graphics.Vty
( Vty(..)
, setWindowTitle
, installCustomWidthTable
, mkVtyFromPair
, module Graphics.Vty.Config
, module Graphics.Vty.Input
, module Graphics.Vty.Input.Events
, module Graphics.Vty.Output
, module Graphics.Vty.Picture
, module Graphics.Vty.Image
, module Graphics.Vty.Attributes
)
where
import Graphics.Vty.Config
import Graphics.Vty.Input
import Graphics.Vty.Input.Events
import Graphics.Vty.Output
import Graphics.Vty.Picture
import Graphics.Vty.Image
import Graphics.Vty.Attributes
import Graphics.Vty.UnicodeWidthTable.IO
import Graphics.Vty.UnicodeWidthTable.Install
import qualified Control.Exception as E
import Control.Monad (when)
import Control.Concurrent.STM
import Data.IORef
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup ((<>))
#endif
data Vty =
Vty { Vty -> Picture -> IO ()
update :: Picture -> IO ()
, Vty -> IO Event
nextEvent :: IO Event
, Vty -> IO (Maybe Event)
nextEventNonblocking :: IO (Maybe Event)
, Vty -> Input
inputIface :: Input
, Vty -> Output
outputIface :: Output
, Vty -> IO ()
refresh :: IO ()
, Vty -> IO ()
shutdown :: IO ()
, Vty -> IO Bool
isShutdown :: IO Bool
}
installCustomWidthTable :: Maybe FilePath
-> Maybe String
-> [(String, FilePath)]
-> IO ()
installCustomWidthTable :: Maybe String -> Maybe String -> [(String, String)] -> IO ()
installCustomWidthTable Maybe String
logPath Maybe String
tblName [(String, String)]
widthMaps = do
let doLog :: String -> IO ()
doLog String
s = case Maybe String
logPath of
Maybe String
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just String
path -> String -> String -> IO ()
appendFile String
path forall a b. (a -> b) -> a -> b
$ String
"installWidthTable: " forall a. Semigroup a => a -> a -> a
<> String
s forall a. Semigroup a => a -> a -> a
<> String
"\n"
Bool
customInstalled <- IO Bool
isCustomTableReady
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
customInstalled) forall a b. (a -> b) -> a -> b
$ do
case Maybe String
tblName of
Maybe String
Nothing ->
String -> IO ()
doLog String
"No terminal name given in the configuration, skipping load"
Just String
name ->
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
name [(String, String)]
widthMaps of
Maybe String
Nothing ->
String -> IO ()
doLog forall a b. (a -> b) -> a -> b
$ String
"Width table " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show String
name forall a. Semigroup a => a -> a -> a
<> String
" not found in custom character width mapping list"
Just String
path -> do
Either SomeException (Either String UnicodeWidthTable)
tableResult <- forall e a. Exception e => IO a -> IO (Either e a)
E.try forall a b. (a -> b) -> a -> b
$ String -> IO (Either String UnicodeWidthTable)
readUnicodeWidthTable String
path
case Either SomeException (Either String UnicodeWidthTable)
tableResult of
Left (SomeException
e::E.SomeException) ->
String -> IO ()
doLog forall a b. (a -> b) -> a -> b
$ String
"Error reading custom character width table " forall a. Semigroup a => a -> a -> a
<>
String
"at " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show String
path forall a. Semigroup a => a -> a -> a
<> String
": " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show SomeException
e
Right (Left String
msg) ->
String -> IO ()
doLog forall a b. (a -> b) -> a -> b
$ String
"Error reading custom character width table " forall a. Semigroup a => a -> a -> a
<>
String
"at " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show String
path forall a. Semigroup a => a -> a -> a
<> String
": " forall a. Semigroup a => a -> a -> a
<> String
msg
Right (Right UnicodeWidthTable
table) -> do
Either SomeException ()
installResult <- forall e a. Exception e => IO a -> IO (Either e a)
E.try forall a b. (a -> b) -> a -> b
$ UnicodeWidthTable -> IO ()
installUnicodeWidthTable UnicodeWidthTable
table
case Either SomeException ()
installResult of
Left (SomeException
e::E.SomeException) ->
String -> IO ()
doLog forall a b. (a -> b) -> a -> b
$ String
"Error installing unicode table (" forall a. Semigroup a => a -> a -> a
<>
forall a. Show a => a -> String
show String
path forall a. Semigroup a => a -> a -> a
<> String
": " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show SomeException
e
Right () ->
String -> IO ()
doLog forall a b. (a -> b) -> a -> b
$ String
"Successfully installed Unicode width table " forall a. Semigroup a => a -> a -> a
<>
String
" from " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show String
path
mkVtyFromPair :: Input -> Output -> IO Vty
mkVtyFromPair :: Input -> Output -> IO Vty
mkVtyFromPair Input
input Output
out = do
Output -> IO ()
reserveDisplay Output
out
TVar Bool
shutdownVar <- forall a. a -> IO (TVar a)
newTVarIO Bool
False
let shutdownIo :: IO ()
shutdownIo = do
Bool
alreadyShutdown <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> a -> STM a
swapTVar TVar Bool
shutdownVar Bool
True
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
alreadyShutdown) forall a b. (a -> b) -> a -> b
$ do
Input -> IO ()
shutdownInput Input
input
Output -> IO ()
releaseDisplay Output
out
Output -> IO ()
releaseTerminal Output
out
shutdownStatus :: IO Bool
shutdownStatus = forall a. TVar a -> IO a
readTVarIO TVar Bool
shutdownVar
IORef (Maybe Picture)
lastPicRef <- forall a. a -> IO (IORef a)
newIORef forall a. Maybe a
Nothing
IORef (Maybe (DisplayRegion, DisplayContext))
lastUpdateRef <- forall a. a -> IO (IORef a)
newIORef forall a. Maybe a
Nothing
let innerUpdate :: Picture -> IO ()
innerUpdate Picture
inPic = do
DisplayRegion
b <- Output -> IO DisplayRegion
displayBounds Output
out
Maybe (DisplayRegion, DisplayContext)
mlastUpdate <- forall a. IORef a -> IO a
readIORef IORef (Maybe (DisplayRegion, DisplayContext))
lastUpdateRef
(DisplayRegion, DisplayContext)
updateData <- case Maybe (DisplayRegion, DisplayContext)
mlastUpdate of
Maybe (DisplayRegion, DisplayContext)
Nothing -> do
DisplayContext
dc <- Output -> DisplayRegion -> IO DisplayContext
displayContext Output
out DisplayRegion
b
DisplayContext -> Picture -> IO ()
outputPicture DisplayContext
dc Picture
inPic
forall (m :: * -> *) a. Monad m => a -> m a
return (DisplayRegion
b, DisplayContext
dc)
Just (DisplayRegion
lastBounds, DisplayContext
lastContext) -> do
if DisplayRegion
b forall a. Eq a => a -> a -> Bool
/= DisplayRegion
lastBounds
then do
DisplayContext
dc <- Output -> DisplayRegion -> IO DisplayContext
displayContext Output
out DisplayRegion
b
DisplayContext -> Picture -> IO ()
outputPicture DisplayContext
dc Picture
inPic
forall (m :: * -> *) a. Monad m => a -> m a
return (DisplayRegion
b, DisplayContext
dc)
else do
DisplayContext -> Picture -> IO ()
outputPicture DisplayContext
lastContext Picture
inPic
forall (m :: * -> *) a. Monad m => a -> m a
return (DisplayRegion
b, DisplayContext
lastContext)
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe (DisplayRegion, DisplayContext))
lastUpdateRef forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (DisplayRegion, DisplayContext)
updateData
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe Picture)
lastPicRef forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Picture
inPic
innerRefresh :: IO ()
innerRefresh = do
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe (DisplayRegion, DisplayContext))
lastUpdateRef forall a. Maybe a
Nothing
DisplayRegion
bounds <- Output -> IO DisplayRegion
displayBounds Output
out
DisplayContext
dc <- Output -> DisplayRegion -> IO DisplayContext
displayContext Output
out DisplayRegion
bounds
forall a. IORef a -> a -> IO ()
writeIORef (Output -> IORef AssumedState
assumedStateRef forall a b. (a -> b) -> a -> b
$ DisplayContext -> Output
contextDevice DisplayContext
dc) AssumedState
initialAssumedState
Maybe Picture
mPic <- forall a. IORef a -> IO a
readIORef IORef (Maybe Picture)
lastPicRef
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return ()) Picture -> IO ()
innerUpdate Maybe Picture
mPic
mkResize :: IO Event
mkResize = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Event
EvResize forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Output -> IO DisplayRegion
displayBounds Output
out
translateInternalEvent :: InternalEvent -> IO Event
translateInternalEvent InternalEvent
ResumeAfterInterrupt = IO Event
mkResize
translateInternalEvent (InputEvent Event
e) = forall (m :: * -> *) a. Monad m => a -> m a
return Event
e
gkey :: IO Event
gkey = do
InternalEvent
e <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TChan a -> STM a
readTChan forall a b. (a -> b) -> a -> b
$ Input -> TChan InternalEvent
eventChannel Input
input
InternalEvent -> IO Event
translateInternalEvent InternalEvent
e
gkey' :: IO (Maybe Event)
gkey' = do
Maybe InternalEvent
mEv <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TChan a -> STM (Maybe a)
tryReadTChan forall a b. (a -> b) -> a -> b
$ Input -> TChan InternalEvent
eventChannel Input
input
case Maybe InternalEvent
mEv of
Just InternalEvent
e -> forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InternalEvent -> IO Event
translateInternalEvent InternalEvent
e
Maybe InternalEvent
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Vty { update :: Picture -> IO ()
update = Picture -> IO ()
innerUpdate
, nextEvent :: IO Event
nextEvent = IO Event
gkey
, nextEventNonblocking :: IO (Maybe Event)
nextEventNonblocking = IO (Maybe Event)
gkey'
, inputIface :: Input
inputIface = Input
input
, outputIface :: Output
outputIface = Output
out
, refresh :: IO ()
refresh = IO ()
innerRefresh
, shutdown :: IO ()
shutdown = IO ()
shutdownIo
, isShutdown :: IO Bool
isShutdown = IO Bool
shutdownStatus
}
setWindowTitle :: Vty -> String -> IO ()
setWindowTitle :: Vty -> String -> IO ()
setWindowTitle Vty
vty String
title =
Output -> String -> IO ()
setOutputWindowTitle (Vty -> Output
outputIface Vty
vty) String
title