Skip to content

Commit

Permalink
Cursor controlled
Browse files Browse the repository at this point in the history
  • Loading branch information
TilakChad committed Feb 9, 2022
1 parent 363c296 commit 83da35a
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 33 deletions.
48 changes: 17 additions & 31 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,23 +3,19 @@ module Main where
import Find as F
import qualified Terminal as Term
import qualified Glob as GlobPattern

import Control.Concurrent
import qualified FileMatch as FMatch
import qualified Data.List as DL
import qualified Glob

import Control.Concurrent
import Control.Monad
import System.IO
import System.Process
import System.IO
import Data.List
import qualified Glob
import Data.Map as Map(keys,lookup)
-- If going for a fuzzy terminal searching, or just as a regular ls thingy
-- It must create some type of virtual environment firt I guess, and when it exit, terminal must switch to its directory


data Content = File String | Folder String | Empty


readKey :: IO [Char]
readKey = reverse <$> readKey' ""
where
Expand All @@ -35,21 +31,12 @@ readKey = reverse <$> readKey' ""

main :: IO ()
main = do
-- args <- Env.getArgs
-- if null args then
-- putStrLn "No source files provided"
-- else
-- listRecursively (head args)
-- Lets try creating some kind of virtual environment where we will be in total control of the terminal
-- color check
-- Let use haskell lazyness for reading keyevents
hSetBuffering stdin NoBuffering
hSetBuffering stdout NoBuffering
hSetEcho stdin False

-- Virtual Environment
-- Lets try working with typeclasses
-- lets try reading arrow keys
-- get key asynchronously and try to interpret it, right...


Expand All @@ -58,6 +45,7 @@ main = do
Term.drawLayout currentPath ""

-- start of the infinite loop .. Don't know how to quit this loop yet .. but
Term.changeCursor Term.SteadyBar
renderTerminal currentPath "" True

update :: String -> Char -> String
Expand All @@ -71,36 +59,34 @@ findmatch path buffer = do
let ffound = filter (`GlobPattern.globmatch` (buffer ++ "*")) files
let dfound = filter (`GlobPattern.globmatch` (buffer ++ "*")) dirs

-- mapM_ (putStrLn . Term.putString Term.Blue) $ filter (`GlobPattern.globmatch` (buffer++"*")) files
-- mapM_ (putStrLn . Term.putString Term.Red) $ filter (`GlobPattern.globmatch` (buffer++"*")) dirs


return $ if null ffound && null dfound then Empty
else
if null ffound then
Folder $ head dfound
else
File $ head ffound

listContents :: String -> String -> IO ()

listContents :: String -> String -> IO String
listContents path buffer = do
let word = words buffer
if length word > 1 then
if head word == "list" then
if length word > 1 && head word == "list" then
do
FMatch.lsh (word !! 1) path
else
listFilesFolders path
return ""
else
listFilesFolders path
do
listFilesFolders path
return buffer


tabAction :: String -> String -> Content -> IO ()
tabAction path buffer Empty = do
-- before that, see if it matches list command
putStrLn ""
listContents path buffer
nbuffer <- listContents path buffer
-- listFilesFolders path
renderTerminal path buffer True
renderTerminal path nbuffer True

tabAction path _ (File file) = do
putStrLn $ "\nExecuting file " ++ file -- TODO :: Execute the file
Expand Down Expand Up @@ -186,8 +172,8 @@ renderTerminal path buffer bRender = do

renderResult :: String -> Content -> IO ()
renderResult _ Empty = return ()
renderResult buffer (File str) = putStr . Term.putString Term.Cyan $ str DL.\\ buffer
renderResult buffer (Folder str) = putStr . Term.putString Term.Cyan $ str DL.\\ buffer
renderResult buffer (File str) = (putStr . Term.putString Term.Cyan $ str DL.\\ buffer) >> Term.moveCursorBack (length $ str DL.\\ buffer)
renderResult buffer (Folder str) = (putStr . Term.putString Term.Cyan $ str DL.\\ buffer) >> Term.moveCursorBack (length $ str DL.\\ buffer)


renderSearch :: FilePath -> String -> IO Content
Expand Down
22 changes: 20 additions & 2 deletions app/Terminal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,8 +66,6 @@ instance Show Keys where
clearTerminal :: IO ()
clearTerminal = return ()



drawLayout :: String -> String -> IO ()
drawLayout path _ = do
clearTerminal
Expand All @@ -88,3 +86,23 @@ executionMap = Map.fromList (zip extension program)

argMap :: Map.Map String [String]
argMap = Map.fromList (zip program args)


data CursorControl = CursorLeft | CursorRight | CursorUp | CursorDown

data CursorShape = BlinkBlock | SteadyBlock | BlinkUnderline | SteadyUnderLine | BlinkBar | SteadyBar | CursorDefault

instance Show CursorShape where
show BlinkBlock = "\ESC[1 q"
show SteadyBlock = "\ESC[2 q"
show BlinkUnderline = "\ESC[3 q"
show SteadyUnderLine = "\ESC[4 q"
show BlinkBar = "\ESC[5 q"
show SteadyBar = "\ESC[6 q"
show _ = "\ESC[0 q"

changeCursor :: CursorShape -> IO ()
changeCursor cs = putStr $ show cs

moveCursorBack :: Int -> IO ()
moveCursorBack n = putStr $ "\ESC[" ++ show n ++ "D"

0 comments on commit 83da35a

Please sign in to comment.