{-# options_haddock prune #-}

-- |Description: Pty Effect, Internal
module Polysemy.Process.Effect.Pty where

import System.IO (Handle)

-- |Horizontal size of a pseudo terminal in characters.
newtype Rows =
  Rows { Rows -> Int
unRows :: Int }
  deriving stock (Rows -> Rows -> Bool
(Rows -> Rows -> Bool) -> (Rows -> Rows -> Bool) -> Eq Rows
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rows -> Rows -> Bool
$c/= :: Rows -> Rows -> Bool
== :: Rows -> Rows -> Bool
$c== :: Rows -> Rows -> Bool
Eq, Int -> Rows -> ShowS
[Rows] -> ShowS
Rows -> String
(Int -> Rows -> ShowS)
-> (Rows -> String) -> ([Rows] -> ShowS) -> Show Rows
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Rows] -> ShowS
$cshowList :: [Rows] -> ShowS
show :: Rows -> String
$cshow :: Rows -> String
showsPrec :: Int -> Rows -> ShowS
$cshowsPrec :: Int -> Rows -> ShowS
Show, (forall x. Rows -> Rep Rows x)
-> (forall x. Rep Rows x -> Rows) -> Generic Rows
forall x. Rep Rows x -> Rows
forall x. Rows -> Rep Rows x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Rows x -> Rows
$cfrom :: forall x. Rows -> Rep Rows x
Generic)
  deriving newtype (Integer -> Rows
Rows -> Rows
Rows -> Rows -> Rows
(Rows -> Rows -> Rows)
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows)
-> (Rows -> Rows)
-> (Rows -> Rows)
-> (Integer -> Rows)
-> Num Rows
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Rows
$cfromInteger :: Integer -> Rows
signum :: Rows -> Rows
$csignum :: Rows -> Rows
abs :: Rows -> Rows
$cabs :: Rows -> Rows
negate :: Rows -> Rows
$cnegate :: Rows -> Rows
* :: Rows -> Rows -> Rows
$c* :: Rows -> Rows -> Rows
- :: Rows -> Rows -> Rows
$c- :: Rows -> Rows -> Rows
+ :: Rows -> Rows -> Rows
$c+ :: Rows -> Rows -> Rows
Num, Num Rows
Ord Rows
Num Rows -> Ord Rows -> (Rows -> Rational) -> Real Rows
Rows -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Rows -> Rational
$ctoRational :: Rows -> Rational
Real, Int -> Rows
Rows -> Int
Rows -> [Rows]
Rows -> Rows
Rows -> Rows -> [Rows]
Rows -> Rows -> Rows -> [Rows]
(Rows -> Rows)
-> (Rows -> Rows)
-> (Int -> Rows)
-> (Rows -> Int)
-> (Rows -> [Rows])
-> (Rows -> Rows -> [Rows])
-> (Rows -> Rows -> [Rows])
-> (Rows -> Rows -> Rows -> [Rows])
-> Enum Rows
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Rows -> Rows -> Rows -> [Rows]
$cenumFromThenTo :: Rows -> Rows -> Rows -> [Rows]
enumFromTo :: Rows -> Rows -> [Rows]
$cenumFromTo :: Rows -> Rows -> [Rows]
enumFromThen :: Rows -> Rows -> [Rows]
$cenumFromThen :: Rows -> Rows -> [Rows]
enumFrom :: Rows -> [Rows]
$cenumFrom :: Rows -> [Rows]
fromEnum :: Rows -> Int
$cfromEnum :: Rows -> Int
toEnum :: Int -> Rows
$ctoEnum :: Int -> Rows
pred :: Rows -> Rows
$cpred :: Rows -> Rows
succ :: Rows -> Rows
$csucc :: Rows -> Rows
Enum, Enum Rows
Real Rows
Real Rows
-> Enum Rows
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows -> (Rows, Rows))
-> (Rows -> Rows -> (Rows, Rows))
-> (Rows -> Integer)
-> Integral Rows
Rows -> Integer
Rows -> Rows -> (Rows, Rows)
Rows -> Rows -> Rows
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Rows -> Integer
$ctoInteger :: Rows -> Integer
divMod :: Rows -> Rows -> (Rows, Rows)
$cdivMod :: Rows -> Rows -> (Rows, Rows)
quotRem :: Rows -> Rows -> (Rows, Rows)
$cquotRem :: Rows -> Rows -> (Rows, Rows)
mod :: Rows -> Rows -> Rows
$cmod :: Rows -> Rows -> Rows
div :: Rows -> Rows -> Rows
$cdiv :: Rows -> Rows -> Rows
rem :: Rows -> Rows -> Rows
$crem :: Rows -> Rows -> Rows
quot :: Rows -> Rows -> Rows
$cquot :: Rows -> Rows -> Rows
Integral, Eq Rows
Eq Rows
-> (Rows -> Rows -> Ordering)
-> (Rows -> Rows -> Bool)
-> (Rows -> Rows -> Bool)
-> (Rows -> Rows -> Bool)
-> (Rows -> Rows -> Bool)
-> (Rows -> Rows -> Rows)
-> (Rows -> Rows -> Rows)
-> Ord Rows
Rows -> Rows -> Bool
Rows -> Rows -> Ordering
Rows -> Rows -> Rows
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Rows -> Rows -> Rows
$cmin :: Rows -> Rows -> Rows
max :: Rows -> Rows -> Rows
$cmax :: Rows -> Rows -> Rows
>= :: Rows -> Rows -> Bool
$c>= :: Rows -> Rows -> Bool
> :: Rows -> Rows -> Bool
$c> :: Rows -> Rows -> Bool
<= :: Rows -> Rows -> Bool
$c<= :: Rows -> Rows -> Bool
< :: Rows -> Rows -> Bool
$c< :: Rows -> Rows -> Bool
compare :: Rows -> Rows -> Ordering
$ccompare :: Rows -> Rows -> Ordering
Ord)

-- |Vertical size of a pseudo terminal in characters.
newtype Cols =
  Cols { Cols -> Int
unCols :: Int }
  deriving stock (Cols -> Cols -> Bool
(Cols -> Cols -> Bool) -> (Cols -> Cols -> Bool) -> Eq Cols
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cols -> Cols -> Bool
$c/= :: Cols -> Cols -> Bool
== :: Cols -> Cols -> Bool
$c== :: Cols -> Cols -> Bool
Eq, Int -> Cols -> ShowS
[Cols] -> ShowS
Cols -> String
(Int -> Cols -> ShowS)
-> (Cols -> String) -> ([Cols] -> ShowS) -> Show Cols
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cols] -> ShowS
$cshowList :: [Cols] -> ShowS
show :: Cols -> String
$cshow :: Cols -> String
showsPrec :: Int -> Cols -> ShowS
$cshowsPrec :: Int -> Cols -> ShowS
Show, (forall x. Cols -> Rep Cols x)
-> (forall x. Rep Cols x -> Cols) -> Generic Cols
forall x. Rep Cols x -> Cols
forall x. Cols -> Rep Cols x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Cols x -> Cols
$cfrom :: forall x. Cols -> Rep Cols x
Generic)
  deriving newtype (Integer -> Cols
Cols -> Cols
Cols -> Cols -> Cols
(Cols -> Cols -> Cols)
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols)
-> (Cols -> Cols)
-> (Cols -> Cols)
-> (Integer -> Cols)
-> Num Cols
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Cols
$cfromInteger :: Integer -> Cols
signum :: Cols -> Cols
$csignum :: Cols -> Cols
abs :: Cols -> Cols
$cabs :: Cols -> Cols
negate :: Cols -> Cols
$cnegate :: Cols -> Cols
* :: Cols -> Cols -> Cols
$c* :: Cols -> Cols -> Cols
- :: Cols -> Cols -> Cols
$c- :: Cols -> Cols -> Cols
+ :: Cols -> Cols -> Cols
$c+ :: Cols -> Cols -> Cols
Num, Num Cols
Ord Cols
Num Cols -> Ord Cols -> (Cols -> Rational) -> Real Cols
Cols -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Cols -> Rational
$ctoRational :: Cols -> Rational
Real, Int -> Cols
Cols -> Int
Cols -> [Cols]
Cols -> Cols
Cols -> Cols -> [Cols]
Cols -> Cols -> Cols -> [Cols]
(Cols -> Cols)
-> (Cols -> Cols)
-> (Int -> Cols)
-> (Cols -> Int)
-> (Cols -> [Cols])
-> (Cols -> Cols -> [Cols])
-> (Cols -> Cols -> [Cols])
-> (Cols -> Cols -> Cols -> [Cols])
-> Enum Cols
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Cols -> Cols -> Cols -> [Cols]
$cenumFromThenTo :: Cols -> Cols -> Cols -> [Cols]
enumFromTo :: Cols -> Cols -> [Cols]
$cenumFromTo :: Cols -> Cols -> [Cols]
enumFromThen :: Cols -> Cols -> [Cols]
$cenumFromThen :: Cols -> Cols -> [Cols]
enumFrom :: Cols -> [Cols]
$cenumFrom :: Cols -> [Cols]
fromEnum :: Cols -> Int
$cfromEnum :: Cols -> Int
toEnum :: Int -> Cols
$ctoEnum :: Int -> Cols
pred :: Cols -> Cols
$cpred :: Cols -> Cols
succ :: Cols -> Cols
$csucc :: Cols -> Cols
Enum, Enum Cols
Real Cols
Real Cols
-> Enum Cols
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols -> (Cols, Cols))
-> (Cols -> Cols -> (Cols, Cols))
-> (Cols -> Integer)
-> Integral Cols
Cols -> Integer
Cols -> Cols -> (Cols, Cols)
Cols -> Cols -> Cols
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Cols -> Integer
$ctoInteger :: Cols -> Integer
divMod :: Cols -> Cols -> (Cols, Cols)
$cdivMod :: Cols -> Cols -> (Cols, Cols)
quotRem :: Cols -> Cols -> (Cols, Cols)
$cquotRem :: Cols -> Cols -> (Cols, Cols)
mod :: Cols -> Cols -> Cols
$cmod :: Cols -> Cols -> Cols
div :: Cols -> Cols -> Cols
$cdiv :: Cols -> Cols -> Cols
rem :: Cols -> Cols -> Cols
$crem :: Cols -> Cols -> Cols
quot :: Cols -> Cols -> Cols
$cquot :: Cols -> Cols -> Cols
Integral, Eq Cols
Eq Cols
-> (Cols -> Cols -> Ordering)
-> (Cols -> Cols -> Bool)
-> (Cols -> Cols -> Bool)
-> (Cols -> Cols -> Bool)
-> (Cols -> Cols -> Bool)
-> (Cols -> Cols -> Cols)
-> (Cols -> Cols -> Cols)
-> Ord Cols
Cols -> Cols -> Bool
Cols -> Cols -> Ordering
Cols -> Cols -> Cols
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Cols -> Cols -> Cols
$cmin :: Cols -> Cols -> Cols
max :: Cols -> Cols -> Cols
$cmax :: Cols -> Cols -> Cols
>= :: Cols -> Cols -> Bool
$c>= :: Cols -> Cols -> Bool
> :: Cols -> Cols -> Bool
$c> :: Cols -> Cols -> Bool
<= :: Cols -> Cols -> Bool
$c<= :: Cols -> Cols -> Bool
< :: Cols -> Cols -> Bool
$c< :: Cols -> Cols -> Bool
compare :: Cols -> Cols -> Ordering
$ccompare :: Cols -> Cols -> Ordering
Ord)

-- |A pseudo terminal, to be scoped with 'withPty'.
data Pty :: Effect where
  -- |The file descriptor that can be connected to stdio of a process.
  Handle :: Pty m Handle
  -- |Set the size of the terminal.
  Resize :: Rows -> Cols -> Pty m ()
  -- |Get the size of the terminal.
  Size :: Pty m (Rows, Cols)

makeSem ''Pty

-- |Bracket an action with the creation and destruction of a pseudo terminal.
withPty ::
  Member (Scoped_ Pty) r =>
  InterpreterFor Pty r
withPty :: forall (r :: EffectRow).
Member (Scoped_ Pty) r =>
InterpreterFor Pty r
withPty =
  Sem (Pty : r) a -> Sem r a
forall (effect :: Effect) (r :: EffectRow).
Member (Scoped_ effect) r =>
InterpreterFor effect r
scoped_