{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Safe #-}
#endif
module System.Console.Terminfo.Cursor(
                        
                        
                        
                        
                        termLines, termColumns,
                        
                        autoRightMargin,
                        autoLeftMargin,
                        wraparoundGlitch,
                        
                        carriageReturn,
                        newline,
                        scrollForward,
                        scrollReverse,
                        
                        
                        
                        
                        
                        
                        moveDown, moveLeft, moveRight, moveUp,
                        
                        
                        
                        
                        cursorDown1, 
                        cursorLeft1,
                        cursorRight1,
                        cursorUp1, 
                        cursorDown, 
                        cursorLeft,
                        cursorRight,
                        cursorUp, 
                        cursorHome,
                        cursorToLL,
                        
                        cursorAddress,
                        Point(..),
                        rowAddress,
                        columnAddress
                        ) where
import System.Console.Terminfo.Base
import Control.Monad
termLines :: Capability Int
termColumns :: Capability Int
termLines :: Capability Int
termLines = String -> Capability Int
tiGetNum String
"lines"
termColumns :: Capability Int
termColumns = String -> Capability Int
tiGetNum String
"cols"
autoRightMargin :: Capability Bool
autoRightMargin :: Capability Bool
autoRightMargin = String -> Capability Bool
tiGetFlag String
"am"
autoLeftMargin :: Capability Bool
autoLeftMargin :: Capability Bool
autoLeftMargin = String -> Capability Bool
tiGetFlag String
"bw"
wraparoundGlitch :: Capability Bool
wraparoundGlitch :: Capability Bool
wraparoundGlitch = String -> Capability Bool
tiGetFlag String
"xenl"
cursorDown1Fixed :: TermStr s => Capability s
cursorDown1Fixed :: forall s. TermStr s => Capability s
cursorDown1Fixed = do
    String
str <- forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"
    forall (f :: * -> *). Alternative f => Bool -> f ()
guard (String
str forall a. Eq a => a -> a -> Bool
/= String
"\n")
    forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"
cursorDown1 :: TermStr s => Capability s
cursorDown1 :: forall s. TermStr s => Capability s
cursorDown1 = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"
cursorLeft1 :: TermStr s => Capability s
cursorLeft1 :: forall s. TermStr s => Capability s
cursorLeft1 = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cub1"
cursorRight1 :: TermStr s => Capability s
cursorRight1 :: forall s. TermStr s => Capability s
cursorRight1 = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cuf1"
cursorUp1 :: TermStr s => Capability s
cursorUp1 :: forall s. TermStr s => Capability s
cursorUp1 = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cuu1"
cursorDown :: TermStr s => Capability (Int -> s)
cursorDown :: forall s. TermStr s => Capability (Int -> s)
cursorDown = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud"
cursorLeft :: TermStr s => Capability (Int -> s)
cursorLeft :: forall s. TermStr s => Capability (Int -> s)
cursorLeft = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cub"
cursorRight :: TermStr s => Capability (Int -> s)
cursorRight :: forall s. TermStr s => Capability (Int -> s)
cursorRight = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cuf"
cursorUp :: TermStr s => Capability (Int -> s)
cursorUp :: forall s. TermStr s => Capability (Int -> s)
cursorUp = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cuu"
cursorHome :: TermStr s => Capability s
cursorHome :: forall s. TermStr s => Capability s
cursorHome = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"home"
cursorToLL :: TermStr s => Capability s
cursorToLL :: forall s. TermStr s => Capability s
cursorToLL = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"ll"
move :: TermStr s => Capability s -> Capability (Int -> s)
                              -> Capability (Int -> s)
move :: forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move Capability s
single Capability (Int -> s)
param = let
        tryBoth :: Capability (Int -> s)
tryBoth = do
                    s
s <- Capability s
single
                    Int -> s
p <- Capability (Int -> s)
param
                    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \Int
n -> case Int
n of
                        Int
0 -> forall a. Monoid a => a
mempty
                        Int
1 -> s
s
                        Int
_ -> Int -> s
p Int
n
        manySingle :: Capability (Int -> s)
manySingle = do
                        s
s <- Capability s
single
                        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \Int
n -> forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a. Int -> a -> [a]
replicate Int
n s
s
        in Capability (Int -> s)
tryBoth forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Capability (Int -> s)
param forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Capability (Int -> s)
manySingle
moveLeft :: TermStr s => Capability (Int -> s)
moveLeft :: forall s. TermStr s => Capability (Int -> s)
moveLeft = forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move forall s. TermStr s => Capability s
cursorLeft1 forall s. TermStr s => Capability (Int -> s)
cursorLeft
moveRight :: TermStr s => Capability (Int -> s)
moveRight :: forall s. TermStr s => Capability (Int -> s)
moveRight = forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move forall s. TermStr s => Capability s
cursorRight1 forall s. TermStr s => Capability (Int -> s)
cursorRight
moveUp :: TermStr s => Capability (Int -> s)
moveUp :: forall s. TermStr s => Capability (Int -> s)
moveUp = forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move forall s. TermStr s => Capability s
cursorUp1 forall s. TermStr s => Capability (Int -> s)
cursorUp
moveDown :: TermStr s => Capability (Int -> s)
moveDown :: forall s. TermStr s => Capability (Int -> s)
moveDown = forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move forall s. TermStr s => Capability s
cursorDown1Fixed forall s. TermStr s => Capability (Int -> s)
cursorDown
carriageReturn :: TermStr s => Capability s
carriageReturn :: forall s. TermStr s => Capability s
carriageReturn = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cr"
newline :: TermStr s => Capability s
newline :: forall s. TermStr s => Capability s
newline = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"nel" 
    forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 forall a. Monoid a => a -> a -> a
mappend forall s. TermStr s => Capability s
carriageReturn 
                            (forall s. TermStr s => Capability s
scrollForward forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"))
        
        
scrollForward :: TermStr s => Capability s
scrollForward :: forall s. TermStr s => Capability s
scrollForward = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"ind"
scrollReverse :: TermStr s => Capability s
scrollReverse :: forall s. TermStr s => Capability s
scrollReverse = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"ri"
data Point = Point {Point -> Int
row, Point -> Int
col :: Int}
cursorAddress :: TermStr s => Capability (Point -> s)
cursorAddress :: forall s. TermStr s => Capability (Point -> s)
cursorAddress = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int -> Int -> s
g Point
p -> Int -> Int -> s
g (Point -> Int
row Point
p) (Point -> Int
col Point
p)) forall a b. (a -> b) -> a -> b
$ forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cup"
columnAddress :: TermStr s => Capability (Int -> s)
columnAddress :: forall s. TermStr s => Capability (Int -> s)
columnAddress = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"hpa"
rowAddress :: TermStr s => Capability (Int -> s)
rowAddress :: forall s. TermStr s => Capability (Int -> s)
rowAddress = forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"vpa"