{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Safe #-}
#endif
-- |
-- Maintainer  : judah.jacobson@gmail.com
-- Stability   : experimental
-- Portability : portable (FFI)
--
-- This module provides capabilities for moving the cursor on the terminal.
module System.Console.Terminfo.Cursor(
                        -- * Terminal dimensions
                        -- | Get the default size of the terminal.  For
                        -- resizeable terminals (e.g., @xterm@), these may not
                        -- correspond to the actual dimensions.
                        termLines, termColumns,
                        -- * Cursor flags
                        autoRightMargin,
                        autoLeftMargin,
                        wraparoundGlitch,
                        -- * Scrolling
                        carriageReturn,
                        newline,
                        scrollForward,
                        scrollReverse,
                        -- * Relative cursor movements
                        -- | The following functions for cursor movement will
                        -- combine the more primitive capabilities.  For example,
                        -- 'moveDown' may use either 'cursorDown' or
                        -- 'cursorDown1' depending on the parameter and which of
                        -- @cud@ and @cud1@ are defined.
                        moveDown, moveLeft, moveRight, moveUp,
                        
                        -- ** Primitive movement capabilities
                        -- | These capabilities correspond directly to @cub@, @cud@,
                        -- @cub1@, @cud1@, etc.
                        cursorDown1, 
                        cursorLeft1,
                        cursorRight1,
                        cursorUp1, 
                        cursorDown, 
                        cursorLeft,
                        cursorRight,
                        cursorUp, 
                        cursorHome,
                        cursorToLL,
                        -- * Absolute cursor movements
                        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"

-- | This flag specifies that the cursor wraps automatically from the last 
-- column of one line to the first column of the next.
autoRightMargin :: Capability Bool
autoRightMargin :: Capability Bool
autoRightMargin = String -> Capability Bool
tiGetFlag String
"am"

-- | This flag specifies that a backspace at column 0 wraps the cursor to
-- the last column of the previous line.
autoLeftMargin :: Capability Bool
autoLeftMargin :: Capability Bool
autoLeftMargin = String -> Capability Bool
tiGetFlag String
"bw"

-- | This flag specifies that the terminal does not perform
-- 'autoRightMargin'-style wrapping when the character which would cause the 
-- wraparound is a control character.
-- This is also known as the \"newline glitch\" or \"magic wrap\".  
-- 
-- For example, in an 80-column terminal with this behavior, the following 
-- will print single-spaced instead of double-spaced:
-- 
-- > replicateM_ 5 $ putStr $ replicate 80 'x' ++ "\n"
-- 
wraparoundGlitch :: Capability Bool
wraparoundGlitch :: Capability Bool
wraparoundGlitch = String -> Capability Bool
tiGetFlag String
"xenl"

{--
On many terminals, the @cud1@ ('cursorDown1') capability is the line feed 
character '\n'.  However, @stty@ settings may cause that character to have
other effects than intended; e.g. ONLCR turns LF into CRLF, and as a result 
@cud1@ will always move the cursor to the first column of the next line.  

Looking at the source code of curses (lib_mvcur.c) and other similar programs, 
they use @cud@ instead of @cud1@ if it's '\n' and ONLCR is turned on.  

Since there's no easy way to check for ONLCR at this point, I've just made
moveDown only use cud1 if it's not '\n'.
Suggestions are welcome.
--}
cursorDown1Fixed :: TermStr s => Capability s
cursorDown1Fixed :: forall s. TermStr s => Capability s
cursorDown1Fixed = do
    String
str <- String -> Capability String
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"
    Bool -> Capability ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (String
str String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"\n")
    String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"

cursorDown1 :: TermStr s => Capability s
cursorDown1 :: forall s. TermStr s => Capability s
cursorDown1 = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"

cursorLeft1 :: TermStr s => Capability s
cursorLeft1 :: forall s. TermStr s => Capability s
cursorLeft1 = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cub1"

cursorRight1 :: TermStr s => Capability s
cursorRight1 :: forall s. TermStr s => Capability s
cursorRight1 = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cuf1"

cursorUp1 :: TermStr s => Capability s
cursorUp1 :: forall s. TermStr s => Capability s
cursorUp1 = String -> Capability s
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 = String -> Capability (Int -> s)
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 = String -> Capability (Int -> s)
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 = String -> Capability (Int -> s)
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 = String -> Capability (Int -> s)
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cuu"

cursorHome :: TermStr s => Capability s
cursorHome :: forall s. TermStr s => Capability s
cursorHome = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"home"

cursorToLL :: TermStr s => Capability s
cursorToLL :: forall s. TermStr s => Capability s
cursorToLL = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"ll"


-- Movements are built out of parametrized and unparam'd movement
-- capabilities.
-- todo: more complicated logic like ncurses does.
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
                    (Int -> s) -> Capability (Int -> s)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int -> s) -> Capability (Int -> s))
-> (Int -> s) -> Capability (Int -> s)
forall a b. (a -> b) -> a -> b
$ \Int
n -> case Int
n of
                        Int
0 -> s
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
                        (Int -> s) -> Capability (Int -> s)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int -> s) -> Capability (Int -> s))
-> (Int -> s) -> Capability (Int -> s)
forall a b. (a -> b) -> a -> b
$ \Int
n -> [s] -> s
forall a. Monoid a => [a] -> a
mconcat ([s] -> s) -> [s] -> s
forall a b. (a -> b) -> a -> b
$ Int -> s -> [s]
forall a. Int -> a -> [a]
replicate Int
n s
s
        in Capability (Int -> s)
tryBoth Capability (Int -> s)
-> Capability (Int -> s) -> Capability (Int -> s)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Capability (Int -> s)
param Capability (Int -> s)
-> Capability (Int -> s) -> Capability (Int -> s)
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 = Capability s -> Capability (Int -> s) -> Capability (Int -> s)
forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move Capability s
forall s. TermStr s => Capability s
cursorLeft1 Capability (Int -> s)
forall s. TermStr s => Capability (Int -> s)
cursorLeft

moveRight :: TermStr s => Capability (Int -> s)
moveRight :: forall s. TermStr s => Capability (Int -> s)
moveRight = Capability s -> Capability (Int -> s) -> Capability (Int -> s)
forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move Capability s
forall s. TermStr s => Capability s
cursorRight1 Capability (Int -> s)
forall s. TermStr s => Capability (Int -> s)
cursorRight

moveUp :: TermStr s => Capability (Int -> s)
moveUp :: forall s. TermStr s => Capability (Int -> s)
moveUp = Capability s -> Capability (Int -> s) -> Capability (Int -> s)
forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move Capability s
forall s. TermStr s => Capability s
cursorUp1 Capability (Int -> s)
forall s. TermStr s => Capability (Int -> s)
cursorUp

moveDown :: TermStr s => Capability (Int -> s)
moveDown :: forall s. TermStr s => Capability (Int -> s)
moveDown = Capability s -> Capability (Int -> s) -> Capability (Int -> s)
forall s.
TermStr s =>
Capability s -> Capability (Int -> s) -> Capability (Int -> s)
move Capability s
forall s. TermStr s => Capability s
cursorDown1Fixed Capability (Int -> s)
forall s. TermStr s => Capability (Int -> s)
cursorDown

-- | The @cr@ capability, which moves the cursor to the first column of the
-- current line.
carriageReturn :: TermStr s => Capability s
carriageReturn :: forall s. TermStr s => Capability s
carriageReturn = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cr"

-- | The @nel@ capability, which moves the cursor to the first column of
-- the next line.  It behaves like a carriage return followed by a line feed.
--
-- If @nel@ is not defined, this may be built out of other capabilities.
newline :: TermStr s => Capability s
newline :: forall s. TermStr s => Capability s
newline = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"nel" 
    Capability s -> Capability s -> Capability s
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` ((s -> s -> s) -> Capability s -> Capability s -> Capability s
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 s -> s -> s
forall a. Monoid a => a -> a -> a
mappend Capability s
forall s. TermStr s => Capability s
carriageReturn 
                            (Capability s
forall s. TermStr s => Capability s
scrollForward Capability s -> Capability s -> Capability s
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"cud1"))
        -- Note it's OK to use cud1 here, despite the stty problem referenced 
        -- above, because carriageReturn already puts us on the first column.

scrollForward :: TermStr s => Capability s
scrollForward :: forall s. TermStr s => Capability s
scrollForward = String -> Capability s
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"ind"

scrollReverse :: TermStr s => Capability s
scrollReverse :: forall s. TermStr s => Capability s
scrollReverse = String -> Capability s
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 = ((Int -> Int -> s) -> Point -> s)
-> Capability (Int -> Int -> s) -> Capability (Point -> s)
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)) (Capability (Int -> Int -> s) -> Capability (Point -> s))
-> Capability (Int -> Int -> s) -> Capability (Point -> s)
forall a b. (a -> b) -> a -> b
$ String -> Capability (Int -> Int -> s)
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 = String -> Capability (Int -> s)
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 = String -> Capability (Int -> s)
forall f. OutputCap f => String -> Capability f
tiGetOutput1 String
"vpa"