{-|

The @files@ command lists included files.

-}

{-# 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


-- | Command line options for this command.
filesmode :: Mode RawOpts
filesmode = CommandDoc
-> [Flag RawOpts]
-> [(CommandDoc, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
  $(embedFileRelative "Hledger/Cli/Commands/Files.txt")
  []
  [(CommandDoc, [Flag RawOpts])
generalflagsgroup2]
  []
  ([], 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
$ CommandDoc -> Arg RawOpts
argsFlag CommandDoc
"[REGEX]")

-- | The files command.
files :: CliOpts -> Journal -> IO ()
files :: CliOpts -> Journal -> IO ()
files CliOpts{rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts} Journal
j = do
  let args :: [CommandDoc]
args = CommandDoc -> RawOpts -> [CommandDoc]
listofstringopt CommandDoc
"args" RawOpts
rawopts
  Maybe Regexp
regex <- (CommandDoc -> IO Regexp) -> Maybe CommandDoc -> IO (Maybe Regexp)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((CommandDoc -> IO Regexp)
-> (Regexp -> IO Regexp) -> Either CommandDoc Regexp -> IO Regexp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either CommandDoc -> IO Regexp
forall (m :: * -> *) a. MonadFail m => CommandDoc -> m a
fail Regexp -> IO Regexp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either CommandDoc Regexp -> IO Regexp)
-> (CommandDoc -> Either CommandDoc Regexp)
-> CommandDoc
-> IO Regexp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either CommandDoc Regexp
toRegex (Text -> Either CommandDoc Regexp)
-> (CommandDoc -> Text) -> CommandDoc -> Either CommandDoc Regexp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandDoc -> Text
T.pack) (Maybe CommandDoc -> IO (Maybe Regexp))
-> Maybe CommandDoc -> IO (Maybe Regexp)
forall a b. (a -> b) -> a -> b
$ [CommandDoc] -> Maybe CommandDoc
forall a. [a] -> Maybe a
headMay [CommandDoc]
args
  let files :: [CommandDoc]
files = ([CommandDoc] -> [CommandDoc])
-> (Regexp -> [CommandDoc] -> [CommandDoc])
-> Maybe Regexp
-> [CommandDoc]
-> [CommandDoc]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [CommandDoc] -> [CommandDoc]
forall a. a -> a
id ((CommandDoc -> Bool) -> [CommandDoc] -> [CommandDoc]
forall a. (a -> Bool) -> [a] -> [a]
filter ((CommandDoc -> Bool) -> [CommandDoc] -> [CommandDoc])
-> (Regexp -> CommandDoc -> Bool)
-> Regexp
-> [CommandDoc]
-> [CommandDoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> CommandDoc -> Bool
regexMatch) Maybe Regexp
regex
              ([CommandDoc] -> [CommandDoc]) -> [CommandDoc] -> [CommandDoc]
forall a b. (a -> b) -> a -> b
$ ((CommandDoc, Text) -> CommandDoc)
-> [(CommandDoc, Text)] -> [CommandDoc]
forall a b. (a -> b) -> [a] -> [b]
map (CommandDoc, Text) -> CommandDoc
forall a b. (a, b) -> a
fst
              ([(CommandDoc, Text)] -> [CommandDoc])
-> [(CommandDoc, Text)] -> [CommandDoc]
forall a b. (a -> b) -> a -> b
$ Journal -> [(CommandDoc, Text)]
jfiles Journal
j
  (CommandDoc -> IO ()) -> [CommandDoc] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CommandDoc -> IO ()
putStrLn [CommandDoc]
files