{-# LINE 1 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
{-# LANGUAGE CApiFFI #-}
module System.Console.Haskeline.Backend.Posix (
withPosixGetEvent,
posixLayouts,
tryGetLayouts,
PosixT,
Handles(),
ehIn,
ehOut,
mapLines,
stdinTTYHandles,
ttyHandles,
posixRunTerm,
fileRunTerm
) where
import Foreign
import Foreign.C.Types
import qualified Data.Map as Map
import System.Posix.Terminal hiding (Interrupt)
import Control.Exception (throwTo)
import Control.Monad
import Control.Monad.Catch (MonadMask, handle, finally)
import Control.Concurrent.STM
import Control.Concurrent hiding (throwTo)
import Data.Maybe (catMaybes)
import System.Posix.Signals.Exts
import System.Posix.Types(Fd(..))
import Data.Foldable (foldl')
import System.IO
import System.Environment
import System.Console.Haskeline.Monads
import System.Console.Haskeline.Key
import System.Console.Haskeline.Term as Term
import System.Console.Haskeline.Prefs
import System.Console.Haskeline.Backend.Posix.Encoder
import GHC.IO.FD (fdFD)
import Data.Typeable (cast)
import System.IO.Error
import GHC.IO.Exception
import GHC.IO.Handle.Types hiding (getState)
import GHC.IO.Handle.Internals
import System.Posix.Internals (FD)
{-# LINE 52 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
data Handles = Handles {Handles -> ExternalHandle
hIn, Handles -> ExternalHandle
hOut :: ExternalHandle
, Handles -> IO ()
closeHandles :: IO ()}
ehIn, ehOut :: Handles -> Handle
ehIn :: Handles -> Handle
ehIn = ExternalHandle -> Handle
eH (ExternalHandle -> Handle)
-> (Handles -> ExternalHandle) -> Handles -> Handle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handles -> ExternalHandle
hIn
ehOut :: Handles -> Handle
ehOut = ExternalHandle -> Handle
eH (ExternalHandle -> Handle)
-> (Handles -> ExternalHandle) -> Handles -> Handle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handles -> ExternalHandle
hOut
{-# LINE 72 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
foreign import capi "sys/ioctl.h ioctl" ioctl :: FD -> CULong -> Ptr a -> IO CInt
posixLayouts :: Handles -> [IO (Maybe Layout)]
posixLayouts :: Handles -> [IO (Maybe Layout)]
posixLayouts Handles
h = [Handle -> IO (Maybe Layout)
ioctlLayout (Handle -> IO (Maybe Layout)) -> Handle -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ Handles -> Handle
ehOut Handles
h, IO (Maybe Layout)
envLayout]
ioctlLayout :: Handle -> IO (Maybe Layout)
ioctlLayout :: Handle -> IO (Maybe Layout)
ioctlLayout Handle
h = Int -> (Ptr (ZonkAny 0) -> IO (Maybe Layout)) -> IO (Maybe Layout)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes ((Int
8)) ((Ptr (ZonkAny 0) -> IO (Maybe Layout)) -> IO (Maybe Layout))
-> (Ptr (ZonkAny 0) -> IO (Maybe Layout)) -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ \Ptr (ZonkAny 0)
ws -> do
{-# LINE 79 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
fd <- Handle -> IO CInt
unsafeHandleToFD Handle
h
ret <- ioctl fd (21523) ws
{-# LINE 81 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
rows :: CUShort <- ((\Ptr (ZonkAny 0)
hsc_ptr -> Ptr (ZonkAny 0) -> Int -> IO CUShort
forall b. Ptr b -> Int -> IO CUShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr (ZonkAny 0)
hsc_ptr Int
0)) ws
{-# LINE 82 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
cols :: CUShort <- ((\Ptr (ZonkAny 0)
hsc_ptr -> Ptr (ZonkAny 0) -> Int -> IO CUShort
forall b. Ptr b -> Int -> IO CUShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr (ZonkAny 0)
hsc_ptr Int
2)) ws
{-# LINE 83 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
if ret >= 0
then return $ Just Layout {height=fromEnum rows,width=fromEnum cols}
else return Nothing
{-# LINE 88 "libraries/haskeline/System/Console/Haskeline/Backend/Posix.hsc" #-}
unsafeHandleToFD :: Handle -> IO FD
unsafeHandleToFD :: Handle -> IO CInt
unsafeHandleToFD Handle
h =
String -> Handle -> (Handle__ -> IO CInt) -> IO CInt
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ String
"unsafeHandleToFd" Handle
h ((Handle__ -> IO CInt) -> IO CInt)
-> (Handle__ -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Handle__{haDevice :: ()
haDevice=dev
dev} -> do
case dev -> Maybe FD
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast dev
dev of
Maybe FD
Nothing -> IOException -> IO CInt
forall a. HasCallStack => IOException -> IO a
ioError (IOException -> String -> IOException
ioeSetErrorString (IOErrorType
-> String -> Maybe Handle -> Maybe String -> IOException
mkIOError IOErrorType
IllegalOperation
String
"unsafeHandleToFd" (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
h) Maybe String
forall a. Maybe a
Nothing)
String
"handle is not a file descriptor")
Just FD
fd -> CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FD -> CInt
fdFD FD
fd)
envLayout :: IO (Maybe Layout)
envLayout :: IO (Maybe Layout)
envLayout = (IOException -> IO (Maybe Layout))
-> IO (Maybe Layout) -> IO (Maybe Layout)
forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
handle (\(IOException
_::IOException) -> Maybe Layout -> IO (Maybe Layout)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Layout
forall a. Maybe a
Nothing) (IO (Maybe Layout) -> IO (Maybe Layout))
-> IO (Maybe Layout) -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ do
r <- String -> IO String
getEnv String
"ROWS"
c <- getEnv "COLUMNS"
return $ Just $ Layout {height=read r,width=read c}
tryGetLayouts :: [IO (Maybe Layout)] -> IO Layout
tryGetLayouts :: [IO (Maybe Layout)] -> IO Layout
tryGetLayouts [] = Layout -> IO Layout
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Layout {height :: Int
height=Int
24,width :: Int
width=Int
80}
tryGetLayouts (IO (Maybe Layout)
f:[IO (Maybe Layout)]
fs) = do
ml <- IO (Maybe Layout)
f
case ml of
Just Layout
l | Layout -> Int
height Layout
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2 Bool -> Bool -> Bool
&& Layout -> Int
width Layout
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2 -> Layout -> IO Layout
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
l
Maybe Layout
_ -> [IO (Maybe Layout)] -> IO Layout
tryGetLayouts [IO (Maybe Layout)]
fs
getKeySequences :: (MonadIO m, MonadReader Prefs m)
=> Handle -> [(String,Key)] -> m (TreeMap Char Key)
getKeySequences :: forall (m :: * -> *).
(MonadIO m, MonadReader Prefs m) =>
Handle -> [(String, Key)] -> m (TreeMap Char Key)
getKeySequences Handle
h [(String, Key)]
tinfos = do
sttys <- IO [(String, Key)] -> m [(String, Key)]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(String, Key)] -> m [(String, Key)])
-> IO [(String, Key)] -> m [(String, Key)]
forall a b. (a -> b) -> a -> b
$ Handle -> IO [(String, Key)]
sttyKeys Handle
h
customKeySeqs <- getCustomKeySeqs
return $ listToTree
$ ansiKeys ++ tinfos ++ sttys ++ customKeySeqs
where
getCustomKeySeqs :: m [(String, Key)]
getCustomKeySeqs = do
kseqs <- (Prefs -> [(Maybe String, String, Key)])
-> m [(Maybe String, String, Key)]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks Prefs -> [(Maybe String, String, Key)]
customKeySequences
termName <- liftIO $ handle (\(IOException
_::IOException) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"") (getEnv "TERM")
let isThisTerm = Bool -> (String -> Bool) -> Maybe String -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
==String
termName)
return $ map (\(Maybe String
_,String
cs,Key
k) ->(String
cs,Key
k))
$ filter (\(Maybe String
kseqs',String
_,Key
_) -> Maybe String -> Bool
isThisTerm Maybe String
kseqs')
$ kseqs
ansiKeys :: [(String, Key)]
ansiKeys :: [(String, Key)]
ansiKeys = [(String
"\ESC[D", BaseKey -> Key
simpleKey BaseKey
LeftKey)
,(String
"\ESC[C", BaseKey -> Key
simpleKey BaseKey
RightKey)
,(String
"\ESC[A", BaseKey -> Key
simpleKey BaseKey
UpKey)
,(String
"\ESC[B", BaseKey -> Key
simpleKey BaseKey
DownKey)
,(String
"\b", BaseKey -> Key
simpleKey BaseKey
Backspace)
,(String
"\ESC[1;5D", Key -> Key
ctrlKey (Key -> Key) -> Key -> Key
forall a b. (a -> b) -> a -> b
$ BaseKey -> Key
simpleKey BaseKey
LeftKey)
,(String
"\ESC[1;5C", Key -> Key
ctrlKey (Key -> Key) -> Key -> Key
forall a b. (a -> b) -> a -> b
$ BaseKey -> Key
simpleKey BaseKey
RightKey)
,(String
"\ESC[5D", Key -> Key
ctrlKey (Key -> Key) -> Key -> Key
forall a b. (a -> b) -> a -> b
$ BaseKey -> Key
simpleKey BaseKey
LeftKey)
,(String
"\ESC[5C", Key -> Key
ctrlKey (Key -> Key) -> Key -> Key
forall a b. (a -> b) -> a -> b
$ BaseKey -> Key
simpleKey BaseKey
RightKey)
,(String
"\ESC[OD", Key -> Key
ctrlKey (Key -> Key) -> Key -> Key
forall a b. (a -> b) -> a -> b
$ BaseKey -> Key
simpleKey BaseKey
LeftKey)
,(String
"\ESC[OC", Key -> Key
ctrlKey (Key -> Key) -> Key -> Key
forall a b. (a -> b) -> a -> b
$ BaseKey -> Key
simpleKey BaseKey
RightKey)
]
sttyKeys :: Handle -> IO [(String, Key)]
sttyKeys :: Handle -> IO [(String, Key)]
sttyKeys Handle
h = do
fd <- Handle -> IO CInt
unsafeHandleToFD Handle
h
attrs <- getTerminalAttributes (Fd fd)
let getStty (ControlCharacter
k,b
c) = do {str <- TerminalAttributes -> ControlCharacter -> Maybe Char
controlChar TerminalAttributes
attrs ControlCharacter
k; return ([str],c)}
return $ catMaybes $ map getStty [(Erase,simpleKey Backspace),(Kill,simpleKey KillLine)]
newtype TreeMap a b = TreeMap (Map.Map a (Maybe b, TreeMap a b))
deriving Int -> TreeMap a b -> ShowS
[TreeMap a b] -> ShowS
TreeMap a b -> String
(Int -> TreeMap a b -> ShowS)
-> (TreeMap a b -> String)
-> ([TreeMap a b] -> ShowS)
-> Show (TreeMap a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> TreeMap a b -> ShowS
forall a b. (Show a, Show b) => [TreeMap a b] -> ShowS
forall a b. (Show a, Show b) => TreeMap a b -> String
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> TreeMap a b -> ShowS
showsPrec :: Int -> TreeMap a b -> ShowS
$cshow :: forall a b. (Show a, Show b) => TreeMap a b -> String
show :: TreeMap a b -> String
$cshowList :: forall a b. (Show a, Show b) => [TreeMap a b] -> ShowS
showList :: [TreeMap a b] -> ShowS
Show
emptyTreeMap :: TreeMap a b
emptyTreeMap :: forall a b. TreeMap a b
emptyTreeMap = Map a (Maybe b, TreeMap a b) -> TreeMap a b
forall a b. Map a (Maybe b, TreeMap a b) -> TreeMap a b
TreeMap Map a (Maybe b, TreeMap a b)
forall k a. Map k a
Map.empty
insertIntoTree :: Ord a => ([a], b) -> TreeMap a b -> TreeMap a b
insertIntoTree :: forall a b. Ord a => ([a], b) -> TreeMap a b -> TreeMap a b
insertIntoTree ([],b
_) TreeMap a b
_ = String -> TreeMap a b
forall a. HasCallStack => String -> a
error String
"Can't insert empty list into a treemap!"
insertIntoTree ((a
c:[a]
cs),b
k) (TreeMap Map a (Maybe b, TreeMap a b)
m) = Map a (Maybe b, TreeMap a b) -> TreeMap a b
forall a b. Map a (Maybe b, TreeMap a b) -> TreeMap a b
TreeMap ((Maybe (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b))
-> a
-> Map a (Maybe b, TreeMap a b)
-> Map a (Maybe b, TreeMap a b)
forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Map.alter Maybe (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b)
f a
c Map a (Maybe b, TreeMap a b)
m)
where
alterSubtree :: TreeMap a b -> TreeMap a b
alterSubtree = ([a], b) -> TreeMap a b -> TreeMap a b
forall a b. Ord a => ([a], b) -> TreeMap a b -> TreeMap a b
insertIntoTree ([a]
cs,b
k)
f :: Maybe (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b)
f Maybe (Maybe b, TreeMap a b)
Nothing = (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b)
forall a. a -> Maybe a
Just ((Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b))
-> (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b)
forall a b. (a -> b) -> a -> b
$ if [a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
cs
then (b -> Maybe b
forall a. a -> Maybe a
Just b
k, TreeMap a b
forall a b. TreeMap a b
emptyTreeMap)
else (Maybe b
forall a. Maybe a
Nothing, TreeMap a b -> TreeMap a b
alterSubtree TreeMap a b
forall a b. TreeMap a b
emptyTreeMap)
f (Just (Maybe b
y,TreeMap a b
t)) = (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b)
forall a. a -> Maybe a
Just ((Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b))
-> (Maybe b, TreeMap a b) -> Maybe (Maybe b, TreeMap a b)
forall a b. (a -> b) -> a -> b
$ if [a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
cs
then (b -> Maybe b
forall a. a -> Maybe a
Just b
k, TreeMap a b
t)
else (Maybe b
y, TreeMap a b -> TreeMap a b
alterSubtree TreeMap a b
t)
listToTree :: Ord a => [([a],b)] -> TreeMap a b
listToTree :: forall a b. Ord a => [([a], b)] -> TreeMap a b
listToTree = (TreeMap a b -> ([a], b) -> TreeMap a b)
-> TreeMap a b -> [([a], b)] -> TreeMap a b
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((([a], b) -> TreeMap a b -> TreeMap a b)
-> TreeMap a b -> ([a], b) -> TreeMap a b
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([a], b) -> TreeMap a b -> TreeMap a b
forall a b. Ord a => ([a], b) -> TreeMap a b -> TreeMap a b
insertIntoTree) TreeMap a b
forall a b. TreeMap a b
emptyTreeMap
mapLines :: (Show a, Show b) => TreeMap a b -> [String]
mapLines :: forall a b. (Show a, Show b) => TreeMap a b -> [String]
mapLines (TreeMap Map a (Maybe b, TreeMap a b)
m) = let
m2 :: Map a [String]
m2 = ((Maybe b, TreeMap a b) -> [String])
-> Map a (Maybe b, TreeMap a b) -> Map a [String]
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (\(Maybe b
k,TreeMap a b
t) -> Maybe b -> String
forall a. Show a => a -> String
show Maybe b
k String -> [String] -> [String]
forall a. a -> [a] -> [a]
: TreeMap a b -> [String]
forall a b. (Show a, Show b) => TreeMap a b -> [String]
mapLines TreeMap a b
t) Map a (Maybe b, TreeMap a b)
m
in ((a, [String]) -> [String]) -> [(a, [String])] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(a
k,[String]
ls) -> a -> String
forall a. Show a => a -> String
show a
k String -> [String] -> [String]
forall a. a -> [a] -> [a]
: ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Char
' 'Char -> ShowS
forall a. a -> [a] -> [a]
:) [String]
ls) ([(a, [String])] -> [String]) -> [(a, [String])] -> [String]
forall a b. (a -> b) -> a -> b
$ Map a [String] -> [(a, [String])]
forall k a. Map k a -> [(k, a)]
Map.toList Map a [String]
m2
lexKeys :: TreeMap Char Key -> [Char] -> [Key]
lexKeys :: TreeMap Char Key -> String -> [Key]
lexKeys TreeMap Char Key
_ [] = []
lexKeys TreeMap Char Key
baseMap String
cs
| Just (Key
k,String
ds) <- TreeMap Char Key -> String -> Maybe (Key, String)
lookupChars TreeMap Char Key
baseMap String
cs
= Key
k Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
: TreeMap Char Key -> String -> [Key]
lexKeys TreeMap Char Key
baseMap String
ds
lexKeys TreeMap Char Key
baseMap (Char
'\ESC':String
cs)
| Key
k:[Key]
ks <- TreeMap Char Key -> String -> [Key]
lexKeys TreeMap Char Key
baseMap String
cs
= Key -> Key
metaKey Key
k Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
: [Key]
ks
lexKeys TreeMap Char Key
baseMap (Char
c:String
cs) = Char -> Key
simpleChar Char
c Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
: TreeMap Char Key -> String -> [Key]
lexKeys TreeMap Char Key
baseMap String
cs
lookupChars :: TreeMap Char Key -> [Char] -> Maybe (Key,[Char])
lookupChars :: TreeMap Char Key -> String -> Maybe (Key, String)
lookupChars TreeMap Char Key
_ [] = Maybe (Key, String)
forall a. Maybe a
Nothing
lookupChars (TreeMap Map Char (Maybe Key, TreeMap Char Key)
tm) (Char
c:String
cs) = case Char
-> Map Char (Maybe Key, TreeMap Char Key)
-> Maybe (Maybe Key, TreeMap Char Key)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Char
c Map Char (Maybe Key, TreeMap Char Key)
tm of
Maybe (Maybe Key, TreeMap Char Key)
Nothing -> Maybe (Key, String)
forall a. Maybe a
Nothing
Just (Maybe Key
Nothing,TreeMap Char Key
t) -> TreeMap Char Key -> String -> Maybe (Key, String)
lookupChars TreeMap Char Key
t String
cs
Just (Just Key
k, t :: TreeMap Char Key
t@(TreeMap Map Char (Maybe Key, TreeMap Char Key)
tm2))
| Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cs) Bool -> Bool -> Bool
&& Bool -> Bool
not (Map Char (Maybe Key, TreeMap Char Key) -> Bool
forall k a. Map k a -> Bool
Map.null Map Char (Maybe Key, TreeMap Char Key)
tm2)
-> TreeMap Char Key -> String -> Maybe (Key, String)
lookupChars TreeMap Char Key
t String
cs
| Bool
otherwise -> (Key, String) -> Maybe (Key, String)
forall a. a -> Maybe a
Just (Key
k, String
cs)
withPosixGetEvent :: (MonadIO m, MonadMask m, MonadReader Prefs m)
=> TChan Event -> Handles -> [(String,Key)]
-> (m Event -> m a) -> m a
withPosixGetEvent :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m, MonadReader Prefs m) =>
TChan Event
-> Handles -> [(String, Key)] -> (m Event -> m a) -> m a
withPosixGetEvent TChan Event
eventChan Handles
h [(String, Key)]
termKeys m Event -> m a
f = Handles -> m a -> m a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
Handles -> m a -> m a
wrapTerminalOps Handles
h (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$ do
baseMap <- Handle -> [(String, Key)] -> m (TreeMap Char Key)
forall (m :: * -> *).
(MonadIO m, MonadReader Prefs m) =>
Handle -> [(String, Key)] -> m (TreeMap Char Key)
getKeySequences (Handles -> Handle
ehIn Handles
h) [(String, Key)]
termKeys
withWindowHandler eventChan
$ f $ liftIO $ getEvent (ehIn h) baseMap eventChan
withWindowHandler :: (MonadIO m, MonadMask m) => TChan Event -> m a -> m a
withWindowHandler :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
TChan Event -> m a -> m a
withWindowHandler TChan Event
eventChan = CInt -> Handler -> m a -> m a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
CInt -> Handler -> m a -> m a
withHandler CInt
windowChange (Handler -> m a -> m a) -> Handler -> m a -> m a
forall a b. (a -> b) -> a -> b
$
IO () -> Handler
Catch (IO () -> Handler) -> IO () -> Handler
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TChan Event -> Event -> STM ()
forall a. TChan a -> a -> STM ()
writeTChan TChan Event
eventChan Event
WindowResize
withSigIntHandler :: (MonadIO m, MonadMask m) => m a -> m a
withSigIntHandler :: forall (m :: * -> *) a. (MonadIO m, MonadMask m) => m a -> m a
withSigIntHandler m a
f = do
tid <- IO ThreadId -> m ThreadId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ThreadId
myThreadId
withHandler keyboardSignal
(Catch (throwTo tid Interrupt))
f
withHandler :: (MonadIO m, MonadMask m) => Signal -> Handler -> m a -> m a
withHandler :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
CInt -> Handler -> m a -> m a
withHandler CInt
signal Handler
handler m a
f = do
old_handler <- IO Handler -> m Handler
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Handler -> m Handler) -> IO Handler -> m Handler
forall a b. (a -> b) -> a -> b
$ CInt -> Handler -> Maybe SignalSet -> IO Handler
installHandler CInt
signal Handler
handler Maybe SignalSet
forall a. Maybe a
Nothing
f `finally` liftIO (installHandler signal old_handler Nothing)
getEvent :: Handle -> TreeMap Char Key -> TChan Event -> IO Event
getEvent :: Handle -> TreeMap Char Key -> TChan Event -> IO Event
getEvent Handle
h TreeMap Char Key
baseMap = IO [Event] -> TChan Event -> IO Event
keyEventLoop (IO [Event] -> TChan Event -> IO Event)
-> IO [Event] -> TChan Event -> IO Event
forall a b. (a -> b) -> a -> b
$ do
cs <- Handle -> IO String
getBlockOfChars Handle
h
return [KeyInput $ lexKeys baseMap cs]
getBlockOfChars :: Handle -> IO String
getBlockOfChars :: Handle -> IO String
getBlockOfChars Handle
h = do
c <- Handle -> IO Char
hGetChar Handle
h
loop [c]
where
loop :: String -> IO String
loop String
cs = do
isReady <- Handle -> IO Bool
hReady Handle
h
if not isReady
then return $ reverse cs
else do
c <- hGetChar h
loop (c:cs)
stdinTTYHandles, ttyHandles :: MaybeT IO Handles
stdinTTYHandles :: MaybeT IO Handles
stdinTTYHandles = do
isInTerm <- IO Bool -> MaybeT IO Bool
forall a. IO a -> MaybeT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> MaybeT IO Bool) -> IO Bool -> MaybeT IO Bool
forall a b. (a -> b) -> a -> b
$ Handle -> IO Bool
hIsTerminalDevice Handle
stdin
guard isInTerm
h <- openTerm WriteMode
return Handles
{ hIn = externalHandle stdin
, hOut = h
, closeHandles = hClose $ eH h
}
ttyHandles :: MaybeT IO Handles
ttyHandles = do
h_in <- IOMode -> MaybeT IO ExternalHandle
openTerm IOMode
ReadMode
h_out <- openTerm WriteMode
return Handles
{ hIn = h_in
, hOut = h_out
, closeHandles = hClose (eH h_in) >> hClose (eH h_out)
}
openTerm :: IOMode -> MaybeT IO ExternalHandle
openTerm :: IOMode -> MaybeT IO ExternalHandle
openTerm IOMode
mode = (IOException -> MaybeT IO ExternalHandle)
-> MaybeT IO ExternalHandle -> MaybeT IO ExternalHandle
forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
handle (\(IOException
_::IOException) -> MaybeT IO ExternalHandle
forall a. MaybeT IO a
forall (m :: * -> *) a. MonadPlus m => m a
mzero)
(MaybeT IO ExternalHandle -> MaybeT IO ExternalHandle)
-> MaybeT IO ExternalHandle -> MaybeT IO ExternalHandle
forall a b. (a -> b) -> a -> b
$ IO ExternalHandle -> MaybeT IO ExternalHandle
forall a. IO a -> MaybeT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ExternalHandle -> MaybeT IO ExternalHandle)
-> IO ExternalHandle -> MaybeT IO ExternalHandle
forall a b. (a -> b) -> a -> b
$ String -> IOMode -> IO ExternalHandle
openInCodingMode String
"/dev/tty" IOMode
mode
posixRunTerm ::
Handles
-> [IO (Maybe Layout)]
-> [(String,Key)]
-> (forall m b . (MonadIO m, MonadMask m) => m b -> m b)
-> (forall m . (MonadMask m, CommandMonad m) => EvalTerm (PosixT m))
-> IO RunTerm
posixRunTerm :: Handles
-> [IO (Maybe Layout)]
-> [(String, Key)]
-> (forall (m :: * -> *) a. (MonadIO m, MonadMask m) => m a -> m a)
-> (forall (m :: * -> *).
(MonadMask m, CommandMonad m) =>
EvalTerm (PosixT m))
-> IO RunTerm
posixRunTerm Handles
hs [IO (Maybe Layout)]
layoutGetters [(String, Key)]
keys forall (m :: * -> *) a. (MonadIO m, MonadMask m) => m a -> m a
wrapGetEvent forall (m :: * -> *).
(MonadMask m, CommandMonad m) =>
EvalTerm (PosixT m)
evalBackend = do
ch <- IO (TChan Event)
forall a. IO (TChan a)
newTChanIO
fileRT <- posixFileRunTerm hs
return fileRT
{ termOps = Left TermOps
{ getLayout = tryGetLayouts layoutGetters
, withGetEvent = wrapGetEvent
. withPosixGetEvent ch hs
keys
, saveUnusedKeys = saveKeys ch
, evalTerm = mapEvalTerm
(runPosixT hs) lift evalBackend
, externalPrint = atomically . writeTChan ch . ExternalPrint
}
, closeTerm = do
flushEventQueue (putStrOut fileRT) ch
closeTerm fileRT
}
type PosixT m = ReaderT Handles m
runPosixT :: Handles -> PosixT m a -> m a
runPosixT :: forall (m :: * -> *) a. Handles -> PosixT m a -> m a
runPosixT Handles
h = Handles -> ReaderT Handles m a -> m a
forall r (m :: * -> *) a. r -> ReaderT r m a -> m a
runReaderT' Handles
h
fileRunTerm :: Handle -> IO RunTerm
fileRunTerm :: Handle -> IO RunTerm
fileRunTerm Handle
h_in = Handles -> IO RunTerm
posixFileRunTerm Handles
{ hIn :: ExternalHandle
hIn = Handle -> ExternalHandle
externalHandle Handle
h_in
, hOut :: ExternalHandle
hOut = Handle -> ExternalHandle
externalHandle Handle
stdout
, closeHandles :: IO ()
closeHandles = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
}
posixFileRunTerm :: Handles -> IO RunTerm
posixFileRunTerm :: Handles -> IO RunTerm
posixFileRunTerm Handles
hs = do
RunTerm -> IO RunTerm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RunTerm
{ putStrOut :: String -> IO ()
putStrOut = \String
str -> ExternalHandle -> IO () -> IO ()
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
ExternalHandle -> m a -> m a
withCodingMode (Handles -> ExternalHandle
hOut Handles
hs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Handle -> String -> IO ()
hPutStr (Handles -> Handle
ehOut Handles
hs) String
str
Handle -> IO ()
hFlush (Handles -> Handle
ehOut Handles
hs)
, closeTerm :: IO ()
closeTerm = Handles -> IO ()
closeHandles Handles
hs
, wrapInterrupt :: forall a (m :: * -> *). (MonadIO m, MonadMask m) => m a -> m a
wrapInterrupt = m a -> m a
forall a (m :: * -> *). (MonadIO m, MonadMask m) => m a -> m a
forall (m :: * -> *) a. (MonadIO m, MonadMask m) => m a -> m a
withSigIntHandler
, termOps :: Either TermOps FileOps
termOps = let h_in :: Handle
h_in = Handles -> Handle
ehIn Handles
hs
in FileOps -> Either TermOps FileOps
forall a b. b -> Either a b
Right FileOps
{ withoutInputEcho :: forall (m :: * -> *) a. (MonadIO m, MonadMask m) => m a -> m a
withoutInputEcho = IO Bool -> (Bool -> IO ()) -> Bool -> m a -> m a
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m) =>
IO a -> (a -> IO ()) -> a -> m b -> m b
bracketSet (Handle -> IO Bool
hGetEcho Handle
h_in)
(Handle -> Bool -> IO ()
hSetEcho Handle
h_in)
Bool
False
, wrapFileInput :: forall a. IO a -> IO a
wrapFileInput = ExternalHandle -> IO a -> IO a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
ExternalHandle -> m a -> m a
withCodingMode (Handles -> ExternalHandle
hIn Handles
hs)
, getLocaleChar :: MaybeT IO Char
getLocaleChar = (Handle -> IO Char) -> Handle -> MaybeT IO Char
forall a. (Handle -> IO a) -> Handle -> MaybeT IO a
guardedEOF Handle -> IO Char
hGetChar Handle
h_in
, maybeReadNewline :: IO ()
maybeReadNewline = Handle -> IO ()
hMaybeReadNewline Handle
h_in
, getLocaleLine :: MaybeT IO String
getLocaleLine = (Handle -> IO String) -> Handle -> MaybeT IO String
forall a. (Handle -> IO a) -> Handle -> MaybeT IO a
guardedEOF Handle -> IO String
hGetLine Handle
h_in
}
}
wrapTerminalOps :: (MonadIO m, MonadMask m) => Handles -> m a -> m a
wrapTerminalOps :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
Handles -> m a -> m a
wrapTerminalOps Handles
hs =
IO BufferMode -> (BufferMode -> IO ()) -> BufferMode -> m a -> m a
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m) =>
IO a -> (a -> IO ()) -> a -> m b -> m b
bracketSet (Handle -> IO BufferMode
hGetBuffering Handle
h_in) (Handle -> BufferMode -> IO ()
hSetBuffering Handle
h_in) BufferMode
NoBuffering
(m a -> m a) -> (m a -> m a) -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO BufferMode -> (BufferMode -> IO ()) -> BufferMode -> m a -> m a
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m) =>
IO a -> (a -> IO ()) -> a -> m b -> m b
bracketSet (Handle -> IO BufferMode
hGetBuffering Handle
h_out) (Handle -> BufferMode -> IO ()
hSetBuffering Handle
h_out) BufferMode
LineBuffering
(m a -> m a) -> (m a -> m a) -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO Bool -> (Bool -> IO ()) -> Bool -> m a -> m a
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m) =>
IO a -> (a -> IO ()) -> a -> m b -> m b
bracketSet (Handle -> IO Bool
hGetEcho Handle
h_in) (Handle -> Bool -> IO ()
hSetEcho Handle
h_in) Bool
False
(m a -> m a) -> (m a -> m a) -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExternalHandle -> m a -> m a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
ExternalHandle -> m a -> m a
withCodingMode (Handles -> ExternalHandle
hIn Handles
hs)
(m a -> m a) -> (m a -> m a) -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExternalHandle -> m a -> m a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
ExternalHandle -> m a -> m a
withCodingMode (Handles -> ExternalHandle
hOut Handles
hs)
where
h_in :: Handle
h_in = Handles -> Handle
ehIn Handles
hs
h_out :: Handle
h_out = Handles -> Handle
ehOut Handles
hs