Lisää komento laskujen listaamiseen

This commit is contained in:
Saku Laesvuori 2025-11-26 19:35:38 +02:00
parent e538c4c69f
commit 19e3573fe8
Signed by: slaesvuo
GPG Key ID: 257D284A2A1D3A32
4 changed files with 52 additions and 2 deletions

View File

@ -26,6 +26,7 @@ executable laskutin
Laskutin,
Laskutin.CSV,
Laskutin.Email,
Laskutin.InvoiceList,
Laskutin.Options,
Laskutin.Status,
Laskutin.Types

View File

@ -23,12 +23,14 @@ import Laskutin.Email
import Laskutin.Options
import Laskutin.Types
import Laskutin.Status
import Laskutin.InvoiceList
main :: IO ()
main = do
Options {csv, command} <- parseOptions
case command of
Status -> statusMain csv
List listOptions -> listMain csv listOptions
Send sendOptions -> sendInvoicesMain csv sendOptions
UpdateTable bankCsv -> updateTableMain csv bankCsv
@ -63,6 +65,11 @@ statusMain invoiceCsv = do
(_, invoices) <- parseCsvFile invoiceCsv
T.putStr $ showStatus $ invoiceStatus invoices
listMain :: FilePath -> ListOptions -> IO ()
listMain invoiceCsv options = do
(_, invoices) <- parseCsvFile invoiceCsv
T.putStr $ showInvoiceList options invoices
updateInvoices :: [CsvTransaction] -> CsvInvoice -> CsvInvoice
updateInvoices transactions invoice@CsvInvoice {reference, ..}
| csvIsPaid invoice = invoice

View File

@ -0,0 +1,33 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Laskutin.InvoiceList (showInvoiceList) where
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.MIME (renderAddress)
import Data.Maybe (mapMaybe, fromMaybe)
import Laskutin.Email (renderInvoiceRow)
import Laskutin.Types (renderEuro, renderReference)
import Laskutin.CSV (CsvInvoice(..), csvInvoiceSum, invoiceRowFromCsv)
import Laskutin.Options (ListOptions(..))
showInvoiceList :: ListOptions -> [CsvInvoice] -> T.Text
showInvoiceList ListOptions {verbose, overpaid} =
T.intercalate separator
. map render
. filter selectors
where render invoice@CsvInvoice {..}
| verbose = "Viite: " <> renderReference reference <> "\n" <>
"Sposti: " <> T.decodeUtf8 (renderAddress invoiceRecipient) <> "\n" <>
"Summa: " <> renderEuro (csvInvoiceSum invoice) <> "\n" <>
"Maksettu: " <> maybe "-" renderEuro paid <> "\n\n" <>
T.intercalate "\n" (renderInvoiceRow <$> mapMaybe invoiceRowFromCsv rows)
| otherwise = renderReference reference <> "\t" <>
T.decodeUtf8 (renderAddress invoiceRecipient) <> "\t" <>
maybe "-" renderEuro paid <> " / " <> renderEuro (csvInvoiceSum invoice)
separator = if verbose then "\n\n---\n\n" else "\n"
selectors = if overpaid then (>) <$> fromMaybe 0 . paid <*> csvInvoiceSum else const True

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoFieldSelectors #-}
module Laskutin.Options (Options(..), SendOptions(..), Command(..), parseOptions) where
module Laskutin.Options (Options(..), SendOptions(..), Command(..), ListOptions(..), parseOptions) where
import Data.Text (Text)
import Data.Time (Day)
@ -22,6 +22,7 @@ data Options = Options
data Command = Send SendOptions
| UpdateTable FilePath
| Status
| List ListOptions
data SendOptions = SendOptions
{ account :: IBAN
@ -35,6 +36,8 @@ data SendOptions = SendOptions
, dryRun :: Bool
}
data ListOptions = ListOptions { verbose :: Bool, overpaid :: Bool}
parseOptions :: IO Options
parseOptions = execParser $ info (options <**> helper)
(fullDesc <> progDesc "Send email invoices from CSV" <> header "laskutin - email invoice sender")
@ -45,7 +48,8 @@ options = Options
<*> subparser
(command "send" (info (sendOptions <**> helper) (progDesc "Send email invoices from CSV"))
<> command "update" (info (updateTableOptions <**> helper) (progDesc "Update invoice CSV from a bank CSV"))
<> command "status" (info (pure Status) (progDesc "Print the status of the invoices")))
<> command "status" (info (pure Status) (progDesc "Print the status of the invoices"))
<> command "list" (info ((List <$> listOptions) <**> helper) (progDesc "List the invoices")))
updateTableOptions :: Parser Command
updateTableOptions = UpdateTable <$> strOption (long "bank-csv" <> metavar "FILE")
@ -62,3 +66,8 @@ sendOptions = fmap Send $ SendOptions
<*> strOption (long "sendmail" <> short 'm' <> metavar "FILE" <> help "The sendmail program to use")
<*> switch (long "reminders" <> short 'r' <> help "Send reminder emails")
<*> switch (long "dry-run" <> short 'd' <> help "Only print what invoices would be sent. Do not send anything")
listOptions :: Parser ListOptions
listOptions = ListOptions
<$> switch (long "verbose" <> short 'v' <> help "Print entire invoices")
<*> switch (long "overpaid" <> short 'o' <> help "Only print overpaid invoices")