Skip to content

Instantly share code, notes, and snippets.

@miguel-negrao
Last active August 29, 2015 14:03
Show Gist options
  • Save miguel-negrao/531dc5dca2525264dedd to your computer and use it in GitHub Desktop.
Save miguel-negrao/531dc5dca2525264dedd to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
module Main where
import System.Environment ( getArgs ) --part of base
import System.Console.GetOpt --part of base
import Shelly (shelly, run_, verbosely, Sh)
import qualified Data.ByteString.Char8 as B
import qualified Data.Text as T
--import qualified Text.ShellEscape as ES
file :: FilePath
file = "/home/miguel/.cmdl.config"
list :: FilePath -> Maybe B.ByteString -> IO ()
list infile ms = do
--B.ByteString
s <- B.readFile infile
--[B.ByteString]
let x = B.lines s
let x2 = zip x [0..length x - 1]
let x3 = maybe x2 (\string -> filter (B.isInfixOf string.fst) x2) ms ::[(B.ByteString, Int)]
let y = B.pack "\n" `pp` B.concat (fmap g x3) `pp` B.pack "\n"
--where g s1 i = (B.pack.show) i `pp` B.pack ": " `pp` (ES.bytes.ES.bash) s1 `pp` B.pack "\n"
where g (s1,i) = (B.pack.show) i `pp` B.pack ": " `pp` s1 `pp` B.pack "\n"
B.putStr y
listAndAsk :: FilePath -> IO ()
listAndAsk infile = do
list infile Nothing
n <- getLine
run file (read n)
pp :: B.ByteString -> B.ByteString -> B.ByteString
pp = B.append
add :: FilePath -> String -> IO ()
add infile cmd = do
s <- B.readFile infile
let new = (if B.last s == '\n' then s else s `pp` "\n") `pp` B.pack cmd `pp` "\n"
B.writeFile file new
addLast :: FilePath -> IO ()
addLast infile = do
s <- B.readFile infile
history <- B.readFile "/home/miguel/.bash_history"
let new = (if B.last s == '\n' then s else s `pp` "\n") `pp` (last.B.lines) history `pp` "\n"
B.writeFile file new
runString :: String -> Sh ()
runString xs = run_ "sh" ["-c", T.pack xs]
--maybe wrap this with a script
run :: FilePath -> Int -> IO()
run infile n = do
s <- B.readFile infile
let x = B.lines s
if length x > n then
shelly $ verbosely $ runString $ B.unpack.(!! n) $ x
else putStrLn "cmd number out of bounds"
get :: FilePath -> Int -> IO()
get infile n = do
s <- B.readFile infile
let x = B.lines s
if length x > n then
B.putStr.(!! n) $ x
else putStr "echo cmd number out of bounds"
--command line option parsing:
data Flag = List (Maybe B.ByteString) | ListAndAsk | Add String | AddLast | Run String | Get String deriving (Eq,Ord,Show)
listp :: Maybe String -> Flag
listp = List . fmap B.pack
options :: [OptDescr Flag]
options =
[ Option "l" ["list"] (OptArg listp "search") "list favorite commands filtered by search"
, Option "a" ["add"] (ReqArg Add "command") "add command to favorites"
, Option "s" ["add-last"] (NoArg AddLast) "add last command to favorites"
, Option "r" ["run"] (ReqArg Run "NUM") "run command"
, Option "g" ["run"] (ReqArg Get "NUM") "get command"
, Option "t" ["listAndAsk"] (NoArg ListAndAsk) "list and ask for command"
]
header :: String
header = "Usage: main [OPTION...]"
main2 :: Flag -> IO()
main2 (List ms) = list file ms
main2 ListAndAsk = listAndAsk file
main2 (Add cmd) = add file $ dropWhile (== ' ') cmd
main2 AddLast = addLast file
main2 (Run n) = run file (read n)
main2 (Get n) = get file (read n)
main :: IO ()
main = do
args <- getArgs
case getOpt RequireOrder options args of
(flags, [], []) -> main2 $ case flags of
[] -> List Nothing
x:_ -> x
(_, nonOpts, []) -> error $ "unrecognized arguments: " ++ unwords nonOpts
(_, _, msgs) -> error $ concat msgs ++ usageInfo header options
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment