#include "Common-Safe-Haskell.hs"
{-# OPTIONS_HADDOCK hide #-}
module System.Console.ANSI.Unix
(
#include "Exports-Include.hs"
) where
import Data.Maybe (fromMaybe)
import Control.Exception.Base (bracket)
import Control.Monad (when)
import System.IO (BufferMode (..), Handle, hGetBuffering, hGetEcho,
hIsTerminalDevice, hIsWritable, hPutStr, hReady, hSetBuffering, hSetEcho,
stdin)
import System.Timeout (timeout)
import Text.ParserCombinators.ReadP (readP_to_S)
import System.Console.ANSI.Codes
import System.Console.ANSI.Types
#include "Common-Include.hs"
#include "Common-Include-Enabled.hs"
hCursorUp h n = hPutStr h $ cursorUpCode n
hCursorDown h n = hPutStr h $ cursorDownCode n
hCursorForward h n = hPutStr h $ cursorForwardCode n
hCursorBackward h n = hPutStr h $ cursorBackwardCode n
hCursorDownLine h n = hPutStr h $ cursorDownLineCode n
hCursorUpLine h n = hPutStr h $ cursorUpLineCode n
hSetCursorColumn h n = hPutStr h $ setCursorColumnCode n
hSetCursorPosition h n m = hPutStr h $ setCursorPositionCode n m
hSaveCursor h = hPutStr h saveCursorCode
hRestoreCursor h = hPutStr h restoreCursorCode
hReportCursorPosition h = hPutStr h reportCursorPositionCode
hClearFromCursorToScreenEnd h = hPutStr h clearFromCursorToScreenEndCode
hClearFromCursorToScreenBeginning h
= hPutStr h clearFromCursorToScreenBeginningCode
hClearScreen h = hPutStr h clearScreenCode
hClearFromCursorToLineEnd h = hPutStr h clearFromCursorToLineEndCode
hClearFromCursorToLineBeginning h = hPutStr h clearFromCursorToLineBeginningCode
hClearLine h = hPutStr h clearLineCode
hScrollPageUp h n = hPutStr h $ scrollPageUpCode n
hScrollPageDown h n = hPutStr h $ scrollPageDownCode n
hSetSGR h sgrs = hPutStr h $ setSGRCode sgrs
hHideCursor h = hPutStr h hideCursorCode
hShowCursor h = hPutStr h showCursorCode
hSetTitle h title = hPutStr h $ setTitleCode title
hSupportsANSI h = (&&) <$> hIsTerminalDevice h <*> isNotDumb
where
isNotDumb = (/= Just "dumb") . lookup "TERM" <$> getEnvironment
hSupportsANSIWithoutEmulation h =
Just <$> ((&&) <$> hIsWritable h <*> hSupportsANSI h)
getReportedCursorPosition = do
fromMaybe "" <$> timeout 500000 get
where
get = do
c <- getChar
if c == '\ESC'
then get' [c]
else return [c]
get' s = do
c <- getChar
if c /= 'R'
then get' (c:s)
else return $ reverse (c:s)
hGetCursorPosition h = fmap to0base <$> getCursorPosition'
where
to0base (row, col) = (row - 1, col - 1)
getCursorPosition' = do
input <- bracket (hGetBuffering stdin) (hSetBuffering stdin) $ \_ -> do
hSetBuffering stdin NoBuffering
bracket (hGetEcho stdin) (hSetEcho stdin) $ \_ -> do
hSetEcho stdin False
clearStdin
hReportCursorPosition h
hFlush h
getReportedCursorPosition
case readP_to_S cursorPosition input of
[] -> return Nothing
[((row, col),_)] -> return $ Just (row, col)
(_:_) -> return Nothing
clearStdin = do
isReady <- hReady stdin
when isReady $ do
_ <-getChar
clearStdin