{-# LANGUAGE TemplateHaskell #-}
module Hledger.Cli.Commands.Files (
filesmode
,files
) where
import qualified Data.Text as T
import Safe (headMay)
import Hledger
import Hledger.Cli.CliOptions
filesmode :: Mode RawOpts
filesmode = CommandHelpStr
-> [Flag RawOpts]
-> [(CommandHelpStr, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
$(embedFileRelative "Hledger/Cli/Commands/Files.txt")
[]
[(CommandHelpStr, [Flag RawOpts])]
cligeneralflagsgroups2
[Flag RawOpts]
hiddenflags
([], Arg RawOpts -> Maybe (Arg RawOpts)
forall a. a -> Maybe a
Just (Arg RawOpts -> Maybe (Arg RawOpts))
-> Arg RawOpts -> Maybe (Arg RawOpts)
forall a b. (a -> b) -> a -> b
$ CommandHelpStr -> Arg RawOpts
argsFlag CommandHelpStr
"[REGEX]")
files :: CliOpts -> Journal -> IO ()
files :: CliOpts -> Journal -> IO ()
files CliOpts{rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts} Journal
j = do
let args :: [CommandHelpStr]
args = CommandHelpStr -> RawOpts -> [CommandHelpStr]
listofstringopt CommandHelpStr
"args" RawOpts
rawopts
Maybe Regexp
regex <- (CommandHelpStr -> IO Regexp)
-> Maybe CommandHelpStr -> IO (Maybe Regexp)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM ((CommandHelpStr -> IO Regexp)
-> (Regexp -> IO Regexp)
-> Either CommandHelpStr Regexp
-> IO Regexp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either CommandHelpStr -> IO Regexp
forall a. CommandHelpStr -> IO a
forall (m :: * -> *) a. MonadFail m => CommandHelpStr -> m a
fail Regexp -> IO Regexp
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either CommandHelpStr Regexp -> IO Regexp)
-> (CommandHelpStr -> Either CommandHelpStr Regexp)
-> CommandHelpStr
-> IO Regexp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either CommandHelpStr Regexp
toRegex (Text -> Either CommandHelpStr Regexp)
-> (CommandHelpStr -> Text)
-> CommandHelpStr
-> Either CommandHelpStr Regexp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandHelpStr -> Text
T.pack) (Maybe CommandHelpStr -> IO (Maybe Regexp))
-> Maybe CommandHelpStr -> IO (Maybe Regexp)
forall a b. (a -> b) -> a -> b
$ [CommandHelpStr] -> Maybe CommandHelpStr
forall a. [a] -> Maybe a
headMay [CommandHelpStr]
args
let fs :: [CommandHelpStr]
fs = ([CommandHelpStr] -> [CommandHelpStr])
-> (Regexp -> [CommandHelpStr] -> [CommandHelpStr])
-> Maybe Regexp
-> [CommandHelpStr]
-> [CommandHelpStr]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [CommandHelpStr] -> [CommandHelpStr]
forall a. a -> a
id ((CommandHelpStr -> Bool) -> [CommandHelpStr] -> [CommandHelpStr]
forall a. (a -> Bool) -> [a] -> [a]
filter ((CommandHelpStr -> Bool) -> [CommandHelpStr] -> [CommandHelpStr])
-> (Regexp -> CommandHelpStr -> Bool)
-> Regexp
-> [CommandHelpStr]
-> [CommandHelpStr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> CommandHelpStr -> Bool
regexMatch) Maybe Regexp
regex
([CommandHelpStr] -> [CommandHelpStr])
-> [CommandHelpStr] -> [CommandHelpStr]
forall a b. (a -> b) -> a -> b
$ ((CommandHelpStr, Text) -> CommandHelpStr)
-> [(CommandHelpStr, Text)] -> [CommandHelpStr]
forall a b. (a -> b) -> [a] -> [b]
map (CommandHelpStr, Text) -> CommandHelpStr
forall a b. (a, b) -> a
fst
([(CommandHelpStr, Text)] -> [CommandHelpStr])
-> [(CommandHelpStr, Text)] -> [CommandHelpStr]
forall a b. (a -> b) -> a -> b
$ Journal -> [(CommandHelpStr, Text)]
jfiles Journal
j
(CommandHelpStr -> IO ()) -> [CommandHelpStr] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CommandHelpStr -> IO ()
putStrLn [CommandHelpStr]
fs