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 = tiGetNum "lines"
termColumns = tiGetNum "columns"
autoRightMargin :: Capability Bool
autoRightMargin = tiGetFlag "am"
autoLeftMargin :: Capability Bool
autoLeftMargin = tiGetFlag "bw"
wraparoundGlitch :: Capability Bool
wraparoundGlitch = tiGetFlag "xenl"
cursorDown1Fixed :: TermStr s => Capability s
cursorDown1Fixed = do
    str <- tiGetOutput1 "cud1"
    guard (str /= "\n")
    tiGetOutput1 "cud1"
cursorDown1 :: TermStr s => Capability s
cursorDown1 = tiGetOutput1 "cud1"
cursorLeft1 :: TermStr s => Capability s
cursorLeft1 = tiGetOutput1 "cub1"
cursorRight1 :: TermStr s => Capability s
cursorRight1 = tiGetOutput1 "cuf1"
cursorUp1 :: TermStr s => Capability s
cursorUp1 = tiGetOutput1 "cuu1"
cursorDown :: TermStr s => Capability (Int -> s)
cursorDown = tiGetOutput1 "cud"
cursorLeft :: TermStr s => Capability (Int -> s)
cursorLeft = tiGetOutput1 "cub"
cursorRight :: TermStr s => Capability (Int -> s)
cursorRight = tiGetOutput1 "cuf"
cursorUp :: TermStr s => Capability (Int -> s)
cursorUp = tiGetOutput1 "cuu"
cursorHome :: TermStr s => Capability s
cursorHome = tiGetOutput1 "home"
cursorToLL :: TermStr s => Capability s
cursorToLL = tiGetOutput1 "ll"
move :: TermStr s => Capability s -> Capability (Int -> s)
                              -> Capability (Int -> s)
move single param = let
        tryBoth = do
                    s <- single
                    p <- param
                    return $ \n -> case n of
                        0 -> mempty
                        1 -> s
                        _ -> p n
        manySingle = do
                        s <- single
                        return $ \n -> mconcat $ replicate n s
        in tryBoth `mplus` param `mplus` manySingle
moveLeft :: TermStr s => Capability (Int -> s)
moveLeft = move cursorLeft1 cursorLeft
moveRight :: TermStr s => Capability (Int -> s)
moveRight = move cursorRight1 cursorRight
moveUp :: TermStr s => Capability (Int -> s)
moveUp = move cursorUp1 cursorUp
moveDown :: TermStr s => Capability (Int -> s)
moveDown = move cursorDown1Fixed cursorDown
carriageReturn :: TermStr s => Capability s
carriageReturn = tiGetOutput1 "cr"
newline :: TermStr s => Capability s
newline = tiGetOutput1 "nel" 
    `mplus` (liftM2 mappend carriageReturn 
                            (scrollForward `mplus` tiGetOutput1 "cud1"))
        
        
scrollForward :: TermStr s => Capability s
scrollForward = tiGetOutput1 "ind"
scrollReverse :: TermStr s => Capability s
scrollReverse = tiGetOutput1 "ri"
data Point = Point {row, col :: Int}
cursorAddress :: TermStr s => Capability (Point -> s)
cursorAddress = fmap (\g p -> g (row p) (col p)) $ tiGetOutput1 "cup"
columnAddress :: TermStr s => Capability (Int -> s)
columnAddress = tiGetOutput1 "hpa"
rowAddress :: TermStr s => Capability (Int -> s)
rowAddress = tiGetOutput1 "vpa"