Skip to content

Commit

Permalink
Add limit functionality, path equals and command equals filter.
Browse files Browse the repository at this point in the history
  • Loading branch information
chrissound committed Nov 17, 2019
1 parent fe514cb commit 70dea39
Show file tree
Hide file tree
Showing 3 changed files with 56 additions and 43 deletions.
10 changes: 9 additions & 1 deletion src/Filter.hs
Expand Up @@ -9,9 +9,11 @@ data Filter = Filter {
pathContains :: [Text]
, pathPrefix :: Maybe Text
, pathSuffix :: Maybe Text
, pathEqual :: Maybe Text
, commandContains :: [Text]
, commandPrefix :: Maybe Text
, commandSuffix :: Maybe Text
, commandEqual :: Maybe Text
, before :: Maybe Text
, after :: Maybe Text
} deriving Show
Expand All @@ -22,11 +24,17 @@ filterRecords f r = Prelude.filter (filterRecord f) r
filterRecord :: Filter -> CommandRecord -> Bool
filterRecord Filter{..} CommandRecord{..} =
Prelude.all (== True)
$
[
Prelude.all (\pc -> isInfixOf (pc) path) pathContains
, maybe True (\x -> isPrefixOf x path) pathPrefix
, maybe True (\x -> isSuffixOf x path) pathSuffix
, Prelude.all (\pc -> isInfixOf (pc) command) commandContains
, maybe True ((==) path) pathEqual
]
<>
[
Prelude.all (\pc -> isInfixOf (pc) command) commandContains
, maybe True (\x -> isPrefixOf x command) commandPrefix
, maybe True (\x -> isSuffixOf x command) commandSuffix
, maybe True ((==) command) commandEqual
]
70 changes: 36 additions & 34 deletions src/Main.hs
Expand Up @@ -48,25 +48,21 @@ target = strOption
<> metavar "TARGET"
<> help "Target for the greeting" )

limiter :: Parser Int
limiter =
option auto (
( long "limit"
<> metavar "NUMBER"
<> help "limit"
<> value 30
)
)

parser :: Parser (IO ())
parser = do
work
<$>
textOption
( long "command"
<> short 'c'
<> metavar "STRING"
<> help "command"
)
<*>
textOption
( long "path"
<> short 'p'
<> metavar "STRING"
<> help "path"
)
<|> printRecords <$> switch ( long "print" <> help "Whether to be quiet" )
-- <|> processPendingFiles <$> switch ( long "process-pending" <> help "" )
printRecords
<$> switch ( long "print" <> help "Whether to be quiet" )
<*> limiter
<|>
printFilterRecords
<$> switch ( long "print-filter" <> help "Print with filter" )
Expand All @@ -93,6 +89,14 @@ parser = do
<> help "command"
)
)
<*>
optional (
textOption
( long "path"
<> metavar "STRING"
<> help "path equals"
)
)
<*> many (
textOption
( long "command-contains"
Expand All @@ -116,6 +120,14 @@ parser = do
<> help "command"
)
)
<*>
optional (
textOption
( long "command"
<> metavar "STRING"
<> help "command equals"
)
)
<*>
optional (
textOption
Expand All @@ -132,31 +144,21 @@ parser = do
<> help "command"
)
)
<*> limiter
<|>
daemon <$> switch ( long "daemon" <> help "Run daemon listener" )


work :: Text -> Text -> IO ()
work a o = do
x <- getCurrentTime
doesFileExist crFile >>= \case
True -> do
decodeFileOrFail crFile >>= \case
Right p -> encodeFile crFile $ CommandRecord a x o : p
Left e -> error $ show e
False -> encodeFile crFile $ [CommandRecord a x o]


printFilterRecords :: Bool
-> [Text] -> Maybe Text -> Maybe Text -- path
-> [Text] -> Maybe Text -> Maybe Text -- command
-> [Text] -> Maybe Text -> Maybe Text -> Maybe Text -- path
-> [Text] -> Maybe Text -> Maybe Text -> Maybe Text -- command
-> Maybe Text -> Maybe Text -- before / after
-> Int
-> IO ()
printFilterRecords _ a b c d e f g h = do
let filter' = Filter a b c d e f g h
printFilterRecords _ pa pb pc pd ca cb cc cd ta tb l = do
let filter' = Filter pa pb pc pd ca cb cc cd ta tb
print filter'
decodeFileOrFail crFile >>= \case
Right p -> do
pp <- getPendingRecords
printRecords' (filterRecords filter' (p ++ pp))
printRecords' (filterRecords filter' (p ++ pp)) l
Left e' -> error $ show e'
19 changes: 11 additions & 8 deletions src/Printer.hs
Expand Up @@ -2,7 +2,7 @@
module Printer where

import Rainbox
import Rainbow ((&))
import Data.Function ((&))
import qualified Rainbow
import Rainbow.Types
import Data.Sequence (Seq)
Expand Down Expand Up @@ -57,7 +57,7 @@ fcol =
Seq.adjust (\x -> x { _background = defaultText}) 0

xyz :: Seq Cell -> Seq Cell
xyz = (Rainbox.intersperse (separator defaultText 1))
xyz = (Seq.intersperse (separator defaultText 1))

myCell :: Rainbow.Radiant -> Rainbow.Radiant -> Alignment Vertical -> Text -> Rainbox.Cell
myCell b f a vv = Rainbox.Cell v Rainbox.top a b
Expand All @@ -67,17 +67,20 @@ myCell b f a vv = Rainbox.Cell v Rainbox.top a b
defaultText :: Rainbow.Radiant
defaultText = Radiant (Color Nothing) (Color Nothing)

printRecords :: Bool -> IO ()
printRecords _ = do
takeLastN :: Int -> [a] -> [a]
takeLastN n = reverse . take n . reverse

printRecords :: Bool -> Int -> IO ()
printRecords _ l = do
decodeFileOrFail crFile >>= \case
Right p -> do
pp <- getPendingRecords
printRecords' (p ++ pp)
printRecords' (p ++ pp) l
Left e -> error $ show e

printRecords' :: [CommandRecord] -> IO ()
printRecords' r = do
let tableV = fmap (renderCr) r
printRecords' :: [CommandRecord] -> Int -> IO ()
printRecords' r l = do
let tableV = fmap (renderCr) $ takeLastN l r
mapM_ Rainbow.putChunk . toList $ render $ horizontalStationTable tableV

renderCr :: CommandRecord -> [String]
Expand Down

0 comments on commit 70dea39

Please sign in to comment.