{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

module Hledger.Cli.Commands.Import (
  importmode
 ,importcmd
)
where

import Control.Monad
import Data.List
import qualified Data.Text.IO as T
import Hledger
import Hledger.Cli.CliOptions
import Hledger.Cli.Commands.Add (journalAddTransaction)
-- import Hledger.Cli.Commands.Print (print')
import System.Console.CmdArgs.Explicit
import Text.Printf

importmode :: Mode RawOpts
importmode = CommandDoc
-> [Flag RawOpts]
-> [(CommandDoc, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
  $(embedFileRelative "Hledger/Cli/Commands/Import.txt")
  [[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"catchup"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"catchup") CommandDoc
"just mark all transactions as already imported"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"dry-run"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"dry-run") CommandDoc
"just show the transactions to be imported"
  ]
  [(CommandDoc, [Flag RawOpts])
generalflagsgroup1]
  [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
$ CommandDoc -> Arg RawOpts
argsFlag CommandDoc
"FILE [...]")

importcmd :: CliOpts -> Journal -> IO ()
importcmd opts :: CliOpts
opts@CliOpts{rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts,inputopts_ :: CliOpts -> InputOpts
inputopts_=InputOpts
iopts} Journal
j = do
  -- XXX could be helpful to show the last-seen date, and number of old transactions, too
  let
    inputfiles :: [CommandDoc]
inputfiles = CommandDoc -> RawOpts -> [CommandDoc]
listofstringopt CommandDoc
"args" RawOpts
rawopts
    inputstr :: CommandDoc
inputstr = CommandDoc -> [CommandDoc] -> CommandDoc
forall a. [a] -> [[a]] -> [a]
intercalate CommandDoc
", " ([CommandDoc] -> CommandDoc) -> [CommandDoc] -> CommandDoc
forall a b. (a -> b) -> a -> b
$ (CommandDoc -> CommandDoc) -> [CommandDoc] -> [CommandDoc]
forall a b. (a -> b) -> [a] -> [b]
map CommandDoc -> CommandDoc
quoteIfNeeded [CommandDoc]
inputfiles
    catchup :: Bool
catchup = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"catchup" RawOpts
rawopts
    dryrun :: Bool
dryrun = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"dry-run" RawOpts
rawopts
    combinedStyles :: Maybe (Map CommoditySymbol AmountStyle)
combinedStyles = 
      let
        maybeInputStyles :: Maybe (Map CommoditySymbol AmountStyle)
maybeInputStyles = BalancingOpts -> Maybe (Map CommoditySymbol AmountStyle)
commodity_styles_ (BalancingOpts -> Maybe (Map CommoditySymbol AmountStyle))
-> (InputOpts -> BalancingOpts)
-> InputOpts
-> Maybe (Map CommoditySymbol AmountStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputOpts -> BalancingOpts
balancingopts_ (InputOpts -> Maybe (Map CommoditySymbol AmountStyle))
-> InputOpts -> Maybe (Map CommoditySymbol AmountStyle)
forall a b. (a -> b) -> a -> b
$ InputOpts
iopts
        inferredStyles :: Map CommoditySymbol AmountStyle
inferredStyles =  Journal -> Map CommoditySymbol AmountStyle
journalCommodityStyles Journal
j
      in
        case Maybe (Map CommoditySymbol AmountStyle)
maybeInputStyles of
          Maybe (Map CommoditySymbol AmountStyle)
Nothing -> Map CommoditySymbol AmountStyle
-> Maybe (Map CommoditySymbol AmountStyle)
forall a. a -> Maybe a
Just Map CommoditySymbol AmountStyle
inferredStyles
          Just Map CommoditySymbol AmountStyle
inputStyles -> Map CommoditySymbol AmountStyle
-> Maybe (Map CommoditySymbol AmountStyle)
forall a. a -> Maybe a
Just (Map CommoditySymbol AmountStyle
 -> Maybe (Map CommoditySymbol AmountStyle))
-> Map CommoditySymbol AmountStyle
-> Maybe (Map CommoditySymbol AmountStyle)
forall a b. (a -> b) -> a -> b
$ Map CommoditySymbol AmountStyle
inputStyles Map CommoditySymbol AmountStyle
-> Map CommoditySymbol AmountStyle
-> Map CommoditySymbol AmountStyle
forall a. Semigroup a => a -> a -> a
<> Map CommoditySymbol AmountStyle
inferredStyles

    iopts' :: InputOpts
iopts' = InputOpts
iopts{new_ :: Bool
new_=Bool
True, new_save_ :: Bool
new_save_=Bool -> Bool
not Bool
dryrun, balancingopts_ :: BalancingOpts
balancingopts_=BalancingOpts
defbalancingopts{commodity_styles_ :: Maybe (Map CommoditySymbol AmountStyle)
commodity_styles_= Maybe (Map CommoditySymbol AmountStyle)
combinedStyles}}
  case [CommandDoc]
inputfiles of
    [] -> CommandDoc -> IO ()
forall a. CommandDoc -> a
error' CommandDoc
"please provide one or more input files as arguments"  -- PARTIAL:
    [CommandDoc]
fs -> do
      Either CommandDoc Journal
enewj <- ExceptT CommandDoc IO Journal -> IO (Either CommandDoc Journal)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT CommandDoc IO Journal -> IO (Either CommandDoc Journal))
-> ExceptT CommandDoc IO Journal -> IO (Either CommandDoc Journal)
forall a b. (a -> b) -> a -> b
$ InputOpts -> [CommandDoc] -> ExceptT CommandDoc IO Journal
readJournalFiles InputOpts
iopts' [CommandDoc]
fs
      case Either CommandDoc Journal
enewj of
        Left CommandDoc
e     -> CommandDoc -> IO ()
forall a. CommandDoc -> a
error' CommandDoc
e
        Right Journal
newj ->
          case (Transaction -> Day) -> [Transaction] -> [Transaction]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Transaction -> Day
tdate ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$ Journal -> [Transaction]
jtxns Journal
newj of
            -- with --dry-run the output should be valid journal format, so messages have ; prepended
            [] -> do
              -- in this case, we vary the output depending on --dry-run, which is a bit awkward
              let semicolon :: CommandDoc
semicolon = if Bool
dryrun then CommandDoc
"; " else CommandDoc
"" :: String
              CommandDoc -> CommandDoc -> CommandDoc -> IO ()
forall r. PrintfType r => CommandDoc -> r
printf CommandDoc
"%sno new transactions found in %s\n\n" CommandDoc
semicolon CommandDoc
inputstr
            [Transaction]
newts | Bool
dryrun -> do
              CommandDoc -> Int -> CommandDoc -> IO ()
forall r. PrintfType r => CommandDoc -> r
printf CommandDoc
"; would import %d new transactions from %s:\n\n" ([Transaction] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Transaction]
newts) CommandDoc
inputstr
              -- TODO how to force output here ?
              -- length (jtxns newj) `seq` print' opts{rawopts_=("explicit",""):rawopts} newj
              (Transaction -> IO ()) -> [Transaction] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (CommoditySymbol -> IO ()
T.putStr (CommoditySymbol -> IO ())
-> (Transaction -> CommoditySymbol) -> Transaction -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> CommoditySymbol
showTransaction) [Transaction]
newts
            [Transaction]
newts | Bool
catchup -> do
              CommandDoc -> CommandDoc -> Int -> IO ()
forall r. PrintfType r => CommandDoc -> r
printf CommandDoc
"marked %s as caught up, skipping %d unimported transactions\n\n" CommandDoc
inputstr ([Transaction] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Transaction]
newts)
            [Transaction]
newts -> do
              -- XXX This writes unix line endings (\n), some at least,
              -- even if the file uses dos line endings (\r\n), which could leave
              -- mixed line endings in the file. See also writeFileWithBackupIfChanged.
              (Journal -> Transaction -> IO Journal)
-> Journal -> [Transaction] -> IO ()
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m ()
foldM_ (Journal -> CliOpts -> Transaction -> IO Journal
`journalAddTransaction` CliOpts
opts) Journal
j [Transaction]
newts  -- gets forced somehow.. (how ?)
              CommandDoc -> Int -> CommandDoc -> IO ()
forall r. PrintfType r => CommandDoc -> r
printf CommandDoc
"imported %d new transactions from %s\n" ([Transaction] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Transaction]
newts) CommandDoc
inputstr