{-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -O2 #-}
module System.Console.Regions (
ConsoleRegion,
RegionLayout(..),
ToRegionContent(..),
RegionContent(..),
LiftRegion(..),
displayConsoleRegions,
withConsoleRegion,
openConsoleRegion,
newConsoleRegion,
closeConsoleRegion,
setConsoleRegion,
appendConsoleRegion,
finishConsoleRegion,
getConsoleRegion,
tuneDisplay,
consoleWidth,
consoleHeight,
regionList,
waitDisplayChange,
) where
import Data.Monoid
import Data.String
import Data.Char
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import qualified Data.Text.IO as T
import Data.Text (Text)
import Control.Monad
import Control.Monad.IO.Class (liftIO, MonadIO)
import Control.Concurrent.STM
import Control.Concurrent.STM.TSem
import Control.Concurrent.Async
import System.Console.ANSI
import qualified System.Console.Terminal.Size as Console
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import Text.Read
import Data.List
#ifndef mingw32_HOST_OS
import System.Posix.Signals
import System.Posix.Signals.Exts
#endif
import Control.Applicative
import Prelude
import System.Console.Concurrent
import Utility.Monad
import Utility.Exception
data RegionLayout = Linear | InLine ConsoleRegion
deriving (Eq)
newtype ConsoleRegion = ConsoleRegion (TVar R)
deriving (Eq)
data R = R
{ regionContent :: RegionContent
, regionRender :: (Text -> STM Text)
, regionLayout :: RegionLayout
, regionChildren :: TVar [ConsoleRegion]
}
newtype RegionContent = RegionContent (STM Text)
{-# NOINLINE regionList #-}
regionList :: TMVar [ConsoleRegion]
regionList = unsafePerformIO newEmptyTMVarIO
{-# NOINLINE consoleSize #-}
consoleSize :: TVar (Console.Window Int)
consoleSize = unsafePerformIO $ newTVarIO $
Console.Window { Console.width = 80, Console.height = 25}
type Width = Int
consoleWidth :: STM Int
consoleWidth = munge . Console.width <$> readTVar consoleSize
where
#ifndef mingw32_HOST_OS
munge = id
#else
munge = pred
#endif
consoleHeight :: STM Int
consoleHeight = Console.height <$> readTVar consoleSize
regionDisplayEnabled :: IO Bool
regionDisplayEnabled = atomically $ not <$> isEmptyTMVar regionList
class LiftRegion m where
liftRegion :: STM a -> m a
instance LiftRegion STM where
liftRegion = id
instance LiftRegion IO where
liftRegion = atomically
class ToRegionContent v where
toRegionContent :: v -> RegionContent
instance ToRegionContent String where
toRegionContent = fromOutput
instance ToRegionContent Text where
toRegionContent = fromOutput
instance ToRegionContent L.Text where
toRegionContent = fromOutput
fromOutput :: Outputable v => v -> RegionContent
fromOutput = RegionContent . pure . toOutput
instance ToRegionContent (STM Text) where
toRegionContent = RegionContent
setConsoleRegion :: (ToRegionContent v, LiftRegion m) => ConsoleRegion -> v -> m ()
setConsoleRegion r v = liftRegion $
modifyRegion r $ const $ pure $ toRegionContent v
appendConsoleRegion :: (Outputable v, LiftRegion m) => ConsoleRegion -> v -> m ()
appendConsoleRegion r v = liftRegion $
modifyRegion r $ \(RegionContent a) ->
return $ RegionContent $ do
t <- a
return (t <> toOutput v)
modifyRegion :: ConsoleRegion -> (RegionContent -> STM RegionContent) -> STM ()
modifyRegion (ConsoleRegion tv) f = do
r <- readTVar tv
rc <- f (regionContent r)
let r' = r { regionContent = rc }
writeTVar tv r'
readRegionContent :: RegionContent -> STM Text
readRegionContent (RegionContent a) = a
resizeRegion :: Width -> ConsoleRegion -> STM [Text]
resizeRegion width (ConsoleRegion tv) = do
r <- readTVar tv
ls <- calcRegionLines r width
return ls
withConsoleRegion :: (MonadIO m, MonadMask m) => RegionLayout -> (ConsoleRegion -> m a) -> m a
withConsoleRegion ly = bracketIO (openConsoleRegion ly) (closeConsoleRegion)
openConsoleRegion :: LiftRegion m => RegionLayout -> m ConsoleRegion
openConsoleRegion ly = liftRegion $ do
h <- newConsoleRegion ly T.empty
case ly of
Linear -> do
ml <- tryTakeTMVar regionList
case ml of
Just l -> putTMVar regionList (h:l)
Nothing -> return ()
InLine parent -> addChild h parent
return h
newConsoleRegion :: (LiftRegion m) => ToRegionContent v => RegionLayout -> v -> m ConsoleRegion
newConsoleRegion ly v = liftRegion $ do
cs <- newTVar mempty
let r = R
{ regionContent = RegionContent $ return mempty
, regionRender = pure
, regionLayout = ly
, regionChildren = cs
}
h <- ConsoleRegion <$> newTVar r
displayChildren h
setConsoleRegion h v
return h
displayChildren :: ConsoleRegion -> STM ()
displayChildren p@(ConsoleRegion tv) = tuneDisplay p $ \t -> do
children <- readTVar . regionChildren =<< readTVar tv
ct <- T.concat <$> mapM getc children
return $ t <> ct
where
getc (ConsoleRegion cv) = do
c <- readTVar cv
regionRender c =<< readRegionContent (regionContent c)
closeConsoleRegion :: LiftRegion m => ConsoleRegion -> m ()
closeConsoleRegion h@(ConsoleRegion tv) = liftRegion $ do
v <- tryTakeTMVar regionList
case v of
Just l ->
let !l' = filter (/= h) l
in putTMVar regionList l'
_ -> return ()
ly <- regionLayout <$> readTVar tv
case ly of
Linear -> return ()
InLine parent -> removeChild h parent
finishConsoleRegion :: (Outputable v, LiftRegion m) => ConsoleRegion -> v -> m ()
finishConsoleRegion h v = liftRegion $ do
closeConsoleRegion h
bufferOutputSTM StdOut (toOutput v <> fromString "\n")
getConsoleRegion :: LiftRegion m => ConsoleRegion -> m Text
getConsoleRegion (ConsoleRegion tv) = liftRegion $
readRegionContent . regionContent =<< readTVar tv
tuneDisplay :: LiftRegion m => ConsoleRegion -> (Text -> STM Text) -> m ()
tuneDisplay (ConsoleRegion tv) renderer = liftRegion $ do
r <- readTVar tv
let rr = \t -> renderer =<< regionRender r t
let r' = r { regionRender = rr }
writeTVar tv r'
addChild :: ConsoleRegion -> ConsoleRegion -> STM ()
addChild child _parent@(ConsoleRegion pv) = do
cv <- regionChildren <$> readTVar pv
children <- readTVar cv
let !children' = filter (/= child) children ++ [child]
writeTVar cv children'
removeChild :: ConsoleRegion -> ConsoleRegion -> STM ()
removeChild child _parent@(ConsoleRegion pv) = do
cv <- regionChildren <$> readTVar pv
modifyTVar' cv (filter (/= child))
displayConsoleRegions :: (MonadIO m, MonadMask m) => m a -> m a
displayConsoleRegions a = ifM (liftIO regionDisplayEnabled)
( a
, lockOutput $ bracket setup cleanup (const a)
)
where
setup = liftIO $ do
atomically $ putTMVar regionList []
endsignal <- atomically $ do
s <- newTSem 1
waitTSem s
return s
isterm <- liftIO $ hSupportsANSI stdout
when isterm trackConsoleWidth
da <- async $ displayThread isterm endsignal
return (isterm, da, endsignal)
cleanup (isterm, da, endsignal) = liftIO $ do
atomically $ signalTSem endsignal
void $ wait da
void $ atomically $ takeTMVar regionList
when isterm $
installResizeHandler Nothing
trackConsoleWidth :: IO ()
trackConsoleWidth = do
let getsz = maybe noop (atomically . writeTVar consoleSize)
=<< Console.size
getsz
installResizeHandler (Just getsz)
data DisplayChange
= BufferChange BufferSnapshot
| RegionChange RegionSnapshot
| RegionListChange RegionSnapshot
| TerminalResize Width
| Shutdown
| DisplayChangeBarrier Barrier
type BufferSnapshot = (StdHandle, OutputBuffer)
type RegionSnapshot = ([ConsoleRegion], [R], [[Text]])
type Barrier = Integer
{-# NOINLINE displayUpdateNotifier #-}
displayUpdateNotifier :: TChan DisplayChange
displayUpdateNotifier = unsafePerformIO $ newBroadcastTChanIO
{-# NOINLINE displayChangeBarrier #-}
displayChangeBarrier :: TVar Barrier
displayChangeBarrier = unsafePerformIO $ newTVarIO 0
waitDisplayChange :: STM a -> IO a
waitDisplayChange a = do
c <- atomically $ dupTChan displayUpdateNotifier
bv <- newEmptyTMVarIO
_ <- setbarrier bv `concurrently` waitchange c bv
snd <$> atomically (readTMVar bv)
where
setbarrier bv = atomically $ do
!b <- succ <$> readTVar displayChangeBarrier
r <- a
writeTVar displayChangeBarrier b
putTMVar bv (b, r)
waitchange c bv = do
change <- atomically $ readTChan c
b <- fst <$> atomically (readTMVar bv)
case change of
DisplayChangeBarrier b' | b' >= b -> return ()
_ -> waitchange c bv
displayThread :: Bool -> TSem -> IO ()
displayThread isterm endsignal = do
origwidth <- atomically consoleWidth
origbarrier <- atomically (readTVar displayChangeBarrier)
go ([], [], []) origwidth origbarrier
where
go origsnapshot@(orighandles, origregions, origlines) origwidth origbarrier = do
let waitwidthchange = do
w <- consoleWidth
if w == origwidth then retry else return w
let waitbarrierchange = do
b <- readTVar displayChangeBarrier
if b /= origbarrier
then return b
else retry
let waitanychange =
(RegionChange <$> regionWaiter origsnapshot origwidth)
`orElse`
(RegionListChange <$> regionListWaiter origsnapshot)
`orElse`
(BufferChange <$> outputBufferWaiterSTM waitCompleteLines)
`orElse`
(TerminalResize <$> waitwidthchange)
`orElse`
(waitTSem endsignal >> pure Shutdown)
`orElse`
(DisplayChangeBarrier <$> waitbarrierchange)
(change, height) <- atomically $ (,)
<$> waitanychange
<*> consoleHeight
let onscreen = take (height - 1) . concat
let update snapshot@(_, _, newlines) = do
when isterm $
changedLines (onscreen origlines) (onscreen newlines)
return $ go snapshot origwidth origbarrier
next <- case change of
RegionChange snapshot -> update snapshot
RegionListChange snapshot -> update snapshot
BufferChange (h, buf) -> do
let origlines' = onscreen origlines
inAreaAbove isterm (length origlines') origlines' $
emitOutputBuffer h buf
return $ go origsnapshot origwidth origbarrier
TerminalResize newwidth -> do
newlines <- atomically (mapM (resizeRegion newwidth) orighandles)
when isterm $ do
resizeRecovery (onscreen newlines)
return $ go (orighandles, origregions, newlines) newwidth origbarrier
Shutdown ->
return $ return ()
DisplayChangeBarrier b ->
return $ go origsnapshot origwidth b
hFlush stdout
atomically $ writeTChan displayUpdateNotifier change
next
readRegions :: [ConsoleRegion] -> STM [R]
readRegions = mapM (\(ConsoleRegion h) -> readTVar h)
regionListWaiter :: RegionSnapshot -> STM RegionSnapshot
regionListWaiter (orighandles, _origregions, origlines) = do
handles <- readTMVar regionList
if handles == orighandles
then retry
else do
rs <- readRegions handles
return (handles, rs, origlines)
regionWaiter :: RegionSnapshot -> Width -> STM RegionSnapshot
regionWaiter (orighandles, _origregions, origlines) width = do
rs <- readRegions orighandles
newlines <- mapM getr rs
unless (newlines /= origlines)
retry
return (orighandles, rs, newlines)
where
getr r = calcRegionLines r width
changedLines :: [Text] -> [Text] -> IO ()
changedLines origlines newlines
| delta == 0 = do
diffUpdate origlines newlines
| delta > 0 = do
let addedlines = reverse (take delta newlines)
displayLines addedlines
let scrolledlines = addedlines ++ origlines
diffUpdate scrolledlines newlines
| otherwise = do
replicateM_ (abs delta) $ do
setCursorColumn 0
cursorUp 1
clearLine
diffUpdate (drop (abs delta) origlines) newlines
where
delta = length newlines - length origlines
diffUpdate :: [Text] -> [Text] -> IO ()
diffUpdate old new = updateLines (zip (zip new changed) old)
where
changed = map (uncurry (/=)) (zip new old) ++ repeat True
changeOffsets :: [((r, Bool), r)] -> Int -> [((r, Int), r)] -> [((r, Int), r)]
changeOffsets [] _ c = reverse c
changeOffsets (((new, changed), old):rs) n c
| changed = changeOffsets rs 1 (((new, n), old):c)
| otherwise = changeOffsets rs (succ n) c
updateLines :: [((Text, Bool), Text)] -> IO ()
updateLines l
| null l' = noop
| otherwise = do
forM_ l' $ \((newt, offset), oldt) -> do
setCursorColumn 0
cursorUp offset
#ifndef mingw32_HOST_OS
T.hPutStr stdout $
genLineUpdate $ calcLineUpdate oldt newt
#else
T.hPutStr stdout newt
clearFromCursorToLineEnd
#endif
cursorDown (sum (map (snd . fst) l'))
setCursorColumn 0
where
l' = changeOffsets l 1 []
resizeRecovery :: [Text] -> IO ()
resizeRecovery newlines = do
setCursorPosition 0 0
inAreaAbove True 0 newlines $
return ()
inAreaAbove :: Bool -> Int -> [Text] -> IO () -> IO ()
inAreaAbove isterm numlines ls outputter = do
when isterm $ do
unless (numlines < 1) $ do
setCursorColumn 0
cursorUp $ numlines
clearFromCursorToScreenEnd
hFlush stdout
outputter
when isterm $ do
setCursorColumn 0
displayLines (reverse ls)
displayLines :: [Text] -> IO ()
displayLines = mapM_ $ \l -> do
T.hPutStr stdout l
putChar '\n'
installResizeHandler :: Maybe (IO ()) -> IO ()
#ifndef mingw32_HOST_OS
installResizeHandler h = void $
installHandler windowChange (maybe Default Catch h) Nothing
#else
installResizeHandler _ = return ()
#endif
calcRegionLines :: R -> Width -> STM [Text]
calcRegionLines r width = do
t <- regionRender r =<< readRegionContent (regionContent r)
return $ reverse $ calcLines t width
calcLines :: Text -> Width -> [Text]
calcLines t width
| width < 1 || T.null t = [t]
| otherwise = calcLines' width [] [] 0 1 (T.length t) t
calcLines' :: Int -> [Text] -> [Text] -> Int -> Int -> Int -> Text -> [Text]
calcLines' width collectedlines collectedSGR i displaysize len t
| i >= len = if i > 0
then reverse (finishline t)
else reverse collectedlines
| t1 == '\n' = calcLines' width (finishline $ T.init currline)
[] 0 1 (T.length rest) (contSGR rest)
| t1 == '\ESC' && i+1 < len = case T.index t (i+1) of
'[' -> skipansi endCSI True
']' -> skipansi endOSC False
_ -> calcLines' width collectedlines collectedSGR (i+1) displaysize len t
| isControl t1 = calcLines' width collectedlines collectedSGR (i+1) displaysize len t
| displaysize >= width = calcLines' width (finishline currline)
[] 0 1 (T.length rest) (contSGR rest)
| otherwise = calcLines' width collectedlines collectedSGR (i+1) (displaysize+1) len t
where
t1 = T.index t i
(currline, rest) = T.splitAt (i+1) t
skipansi toend isCSI = case T.findIndex toend (T.drop (i+2) t) of
Just csiend -> calcLines' width collectedlines
(addSGR (csiend+2)) (i+2+csiend) (displaysize-1) len t
Nothing -> reverse (finishline t)
where
addSGR csiend
| not isCSI = collectedSGR
| ansicode == resetSGR = []
| not (T.null ansicode) && T.last ansicode == endSGR =
ansicode : collectedSGR
| otherwise = collectedSGR
where
ansicode = T.take (csiend + 1) (T.drop i t)
finishline l = closeSGR l : collectedlines
closeSGR l
| null collectedSGR = l
| otherwise = l <> resetSGR
contSGR l = mconcat (reverse collectedSGR) <> l
resetSGR :: Text
resetSGR = T.pack (setSGRCode [Reset])
endCSI :: Char -> Bool
endCSI c = let o = ord c in o >= 64 && o < 127
endOSC :: Char -> Bool
endOSC c = c == '\BEL'
endSGR :: Char
endSGR = 'm'
calcLineUpdate :: Text -> Text -> [LineUpdate]
calcLineUpdate old new =
reverse $ go
(advanceLine old [] [])
(advanceLine new [] [])
where
go (Just _, _, _, _) (Nothing, _, past, _) = ClearToEnd : past
go (Nothing, _, _, _) (Nothing, _, past, _) = past
go (Nothing, _, _, _) (Just n, ns, past, _) =
Display ns : Display (T.singleton n) : past
go (Just o, os, _, oinvis) (Just n, ns, past, ninvis)
| o == n && oinvis == ninvis = go
(advanceLine os [] oinvis)
(advanceLine ns (Skip [o] : past) ninvis)
| otherwise = go
(advanceLine os [] oinvis)
(advanceLine ns (Display (T.singleton n) : past) ninvis)
type Past = [LineUpdate]
type Invis = [LineUpdate]
advanceLine :: Text -> Past -> Invis -> (Maybe Char, Text, Past, Invis)
advanceLine t past invis
| T.null t = (Nothing, T.empty, past, invis)
| otherwise = case T.head t of
'\ESC' -> case T.drop 1 t of
t' | T.null t' -> advanceLine (T.drop 1 t)
(Skip "\ESC":past) (Skip "\ESC":invis)
| otherwise -> case T.head t' of
'[' -> skipansi endCSI
']' -> skipansi endOSC
c -> (Just c, T.drop 2 t, Skip "\ESC":past, Skip "\ESC":invis)
c | isControl c -> advanceLine (T.drop 1 t) (Skip [c]:past) (Skip [c]:invis)
| otherwise -> (Just c, T.drop 1 t, past, invis)
where
skipansi toend = case T.findIndex toend (T.drop 2 t) of
Just csiend ->
let sgr = SGR (T.take (csiend+3) t)
in advanceLine (T.drop (csiend+3) t)
(sgr:past) (addsgr sgr invis)
Nothing -> (Nothing, T.empty, past, invis)
addsgr (SGR sgrt) l
| sgrt == resetSGR = filter (not . isSGR) l
addsgr s l = s:l
data LineUpdate = Display Text | Skip [Char] | SGR Text | ClearToEnd
deriving (Eq, Show)
isSGR :: LineUpdate -> Bool
isSGR (SGR _) = True
isSGR _ = False
genLineUpdate :: [LineUpdate] -> Text
genLineUpdate l = T.concat $ map tot (optimiseLineUpdate l)
where
tot (Display t) = t
tot (Skip s)
| len < 5 = T.pack s
| otherwise = T.pack (cursorForwardCode len)
where
len = length s
tot (SGR t) = t
tot ClearToEnd = T.pack clearFromCursorToLineEndCode
optimiseLineUpdate :: [LineUpdate] -> [LineUpdate]
optimiseLineUpdate = go []
where
go (Skip _:rest) [] = go rest []
go (SGR t:rest) [] | t /= resetSGR = go rest []
go c [] = reverse c
go c (SGR t1:Skip s:SGR t2:rest) = tryharder c (SGR (combineSGR t1 t2):Skip s:rest)
go c (Skip s:Skip s':rest) = tryharder c (Skip (s++s'):rest)
go c (SGR t1:SGR t2:rest) = tryharder c (SGR (combineSGR t1 t2):rest)
go c (v:rest) = go (v:c) rest
tryharder c l = go [] (reverse c ++ l)
combineSGR :: Text -> Text -> Text
combineSGR a b = case combineSGRCodes (codes a) (codes b) of
Nothing -> a <> b
Just cs -> T.pack $ "\ESC[" ++ intercalate ";" (map show cs) ++ "m"
where
codes = map (readMaybe . T.unpack) .
T.split (== ';') . T.drop 2 . T.init
combineSGRCodes :: [Maybe Int] -> [Maybe Int] -> Maybe [Int]
combineSGRCodes as bs =
map snd . nubBy (\a b -> fst a == fst b) <$> mapM range (reverse bs ++ reverse as)
where
range Nothing = Nothing
range (Just x)
| x >= 30 && x <= 37 = Just (Foreground, x)
| x >= 40 && x <= 47 = Just (Background, x)
| x >= 90 && x <= 97 = Just (Foreground, x)
| x >= 100 && x <= 107 = Just (Background, x)
| otherwise = Nothing