Skip to content

Instantly share code, notes, and snippets.

@soupi
Created October 9, 2015 13:07
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save soupi/199a16be6e2071c3b724 to your computer and use it in GitHub Desktop.
Save soupi/199a16be6e2071c3b724 to your computer and use it in GitHub Desktop.
a file reader similar to less
module Main where
import System.IO (hSetBuffering, stdin, BufferMode(NoBuffering))
import Control.Monad (unless)
import System.Process (system)
import System.Environment (getArgs)
stepSize :: Int
stepSize = 30
data State
= State
{ previousLines :: [String]
, currentLines :: [String]
, nextLines :: [String]
}
main :: IO ()
main = do
arguments <- getArgs
case arguments of
[file] -> do
fileContent <- readFile file
hSetBuffering stdin NoBuffering
_ <- system "tput smcup" -- OS command to open alternate screen
_ <- system "clear"
let state = State [] [] (lines fileContent)
let newState@(State { currentLines=cl }) = move stepSize state
putStrLn (unlines cl)
run newState
_ <- system "tput rmcup" -- OS command to close alternate screen
pure ()
_ ->
putStrLn usageMessage
usageMessage :: String
usageMessage =
"Usage: runhaskell Less.hs <file>"
run :: State-> IO ()
run state = do
putStrLn "\n(q/ESC to quit, h/j/k/l to move)"
cmdChar <- getChar
let newState@(State { currentLines=cl }) = getnextLines cmdChar state
_ <- system "clear"
putStrLn (unlines cl)
unless (cmdChar == 'q' || cmdChar == '\ESC') (run newState)
getnextLines :: Char -> State -> State
getnextLines ch state
| ch == 'j' = move 1 state
| ch == 'k' = move (-1) state
| ch == 'l' = move stepSize state
| ch == 'h' = move (-stepSize) state
| otherwise = state
move :: Int -> State -> State
move numOfSteps =
if numOfSteps < 0
then moveBackward (-numOfSteps)
else moveForward numOfSteps
moveForward :: Int -> State -> State
moveForward numOfLines state@(State prev curr next) =
let step = min numOfLines (length next)
in
state { previousLines = prev ++ take step curr
, currentLines = drop step curr ++ take step next
, nextLines = drop step next
}
moveBackward :: Int -> State -> State
moveBackward numOfLines state@(State prev curr next) =
let step = min numOfLines (length prev)
in
state { previousLines = take (length prev - step) prev
, currentLines = drop (length prev - step) prev ++ take (length curr - step) curr
, nextLines = drop (length curr - step) curr ++ next
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment