{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Hledger.Data.PeriodicTransaction (
runPeriodicTransaction
, checkPeriodicTransactionStartDate
)
where
import Data.Function ((&))
import Data.Maybe (isNothing)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Text.Printf
import Hledger.Data.Types
import Hledger.Data.Dates
import Hledger.Data.Amount
import Hledger.Data.Posting (post, generatedTransactionTagName)
import Hledger.Data.Transaction
_ptgen :: [Char] -> IO ()
_ptgen [Char]
str = do
let
t :: AccountName
t = [Char] -> AccountName
T.pack [Char]
str
(Interval
i,DateSpan
s) = Day -> AccountName -> (Interval, DateSpan)
parsePeriodExpr' Day
nulldate AccountName
t
(Transaction -> IO ()) -> [Transaction] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (AccountName -> IO ()
T.putStr (AccountName -> IO ())
-> (Transaction -> AccountName) -> Transaction -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> AccountName
showTransaction) ([Transaction] -> IO ()) -> [Transaction] -> IO ()
forall a b. (a -> b) -> a -> b
$
Bool -> PeriodicTransaction -> DateSpan -> [Transaction]
runPeriodicTransaction Bool
True
PeriodicTransaction
nullperiodictransaction{ ptperiodexpr=t , ptspan=s, ptinterval=i, ptpostings=["a" `post` usd 1] }
DateSpan
nulldatespan
_ptgenspan :: [Char] -> DateSpan -> IO ()
_ptgenspan [Char]
str DateSpan
spn = do
let
t :: AccountName
t = [Char] -> AccountName
T.pack [Char]
str
(Interval
i,DateSpan
s) = Day -> AccountName -> (Interval, DateSpan)
parsePeriodExpr' Day
nulldate AccountName
t
(Transaction -> IO ()) -> [Transaction] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (AccountName -> IO ()
T.putStr (AccountName -> IO ())
-> (Transaction -> AccountName) -> Transaction -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> AccountName
showTransaction) ([Transaction] -> IO ()) -> [Transaction] -> IO ()
forall a b. (a -> b) -> a -> b
$
Bool -> PeriodicTransaction -> DateSpan -> [Transaction]
runPeriodicTransaction Bool
True
PeriodicTransaction
nullperiodictransaction{ ptperiodexpr=t , ptspan=s, ptinterval=i, ptpostings=["a" `post` usd 1] }
DateSpan
spn
instance Show PeriodicTransaction where
show :: PeriodicTransaction -> [Char]
show PeriodicTransaction{[Tag]
[Posting]
(SourcePos, SourcePos)
AccountName
Status
Interval
DateSpan
ptperiodexpr :: PeriodicTransaction -> AccountName
ptspan :: PeriodicTransaction -> DateSpan
ptinterval :: PeriodicTransaction -> Interval
ptpostings :: PeriodicTransaction -> [Posting]
ptperiodexpr :: AccountName
ptinterval :: Interval
ptspan :: DateSpan
ptsourcepos :: (SourcePos, SourcePos)
ptstatus :: Status
ptcode :: AccountName
ptdescription :: AccountName
ptcomment :: AccountName
pttags :: [Tag]
ptpostings :: [Posting]
ptsourcepos :: PeriodicTransaction -> (SourcePos, SourcePos)
ptstatus :: PeriodicTransaction -> Status
ptcode :: PeriodicTransaction -> AccountName
ptdescription :: PeriodicTransaction -> AccountName
ptcomment :: PeriodicTransaction -> AccountName
pttags :: PeriodicTransaction -> [Tag]
..} =
[Char]
-> [Char]
-> [Char]
-> [Char]
-> [Char]
-> [Char]
-> [Char]
-> [Char]
-> [Char]
-> [Char]
-> ShowS
forall r. PrintfType r => [Char] -> r
printf [Char]
"PeriodicTransactionPP {%s, %s, %s, %s, %s, %s, %s, %s, %s, %s}"
([Char]
"ptperiodexpr=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ AccountName -> [Char]
forall a. Show a => a -> [Char]
show AccountName
ptperiodexpr)
([Char]
"ptinterval=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Interval -> [Char]
forall a. Show a => a -> [Char]
show Interval
ptinterval)
([Char]
"ptspan=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> [Char]
show (DateSpan -> [Char]
forall a. Show a => a -> [Char]
show DateSpan
ptspan))
([Char]
"ptsourcepos=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ (SourcePos, SourcePos) -> [Char]
forall a. Show a => a -> [Char]
show (SourcePos, SourcePos)
ptsourcepos)
([Char]
"ptstatus=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> [Char]
show (Status -> [Char]
forall a. Show a => a -> [Char]
show Status
ptstatus))
([Char]
"ptcode=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ AccountName -> [Char]
forall a. Show a => a -> [Char]
show AccountName
ptcode)
([Char]
"ptdescription=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ AccountName -> [Char]
forall a. Show a => a -> [Char]
show AccountName
ptdescription)
([Char]
"ptcomment=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ AccountName -> [Char]
forall a. Show a => a -> [Char]
show AccountName
ptcomment)
([Char]
"pttags=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Tag] -> [Char]
forall a. Show a => a -> [Char]
show [Tag]
pttags)
([Char]
"ptpostings=" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Posting] -> [Char]
forall a. Show a => a -> [Char]
show [Posting]
ptpostings)
runPeriodicTransaction :: Bool -> PeriodicTransaction -> DateSpan -> [Transaction]
runPeriodicTransaction :: Bool -> PeriodicTransaction -> DateSpan -> [Transaction]
runPeriodicTransaction Bool
verbosetags PeriodicTransaction{[Tag]
[Posting]
(SourcePos, SourcePos)
AccountName
Status
Interval
DateSpan
ptperiodexpr :: PeriodicTransaction -> AccountName
ptspan :: PeriodicTransaction -> DateSpan
ptinterval :: PeriodicTransaction -> Interval
ptpostings :: PeriodicTransaction -> [Posting]
ptsourcepos :: PeriodicTransaction -> (SourcePos, SourcePos)
ptstatus :: PeriodicTransaction -> Status
ptcode :: PeriodicTransaction -> AccountName
ptdescription :: PeriodicTransaction -> AccountName
ptcomment :: PeriodicTransaction -> AccountName
pttags :: PeriodicTransaction -> [Tag]
ptperiodexpr :: AccountName
ptinterval :: Interval
ptspan :: DateSpan
ptsourcepos :: (SourcePos, SourcePos)
ptstatus :: Status
ptcode :: AccountName
ptdescription :: AccountName
ptcomment :: AccountName
pttags :: [Tag]
ptpostings :: [Posting]
..} DateSpan
requestedspan =
[ Transaction
t{tdate=d} | (DateSpan (Just EFDay
efd) Maybe EFDay
_) <- [DateSpan]
alltxnspans, let d :: Day
d = EFDay -> Day
fromEFDay EFDay
efd, DateSpan -> Day -> Bool
spanContainsDate DateSpan
requestedspan Day
d ]
where
t :: Transaction
t = Transaction
nulltransaction{
tsourcepos = ptsourcepos
,tstatus = ptstatus
,tcode = ptcode
,tdescription = ptdescription
,tcomment = ptcomment
,ttags = pttags
,tpostings = ptpostings
}
Transaction -> (Transaction -> Transaction) -> Transaction
forall a b. a -> (a -> b) -> b
& Bool -> Tag -> Transaction -> Transaction
transactionAddHiddenAndMaybeVisibleTag Bool
verbosetags (AccountName
generatedTransactionTagName, AccountName
period)
period :: AccountName
period = AccountName
"~ " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
ptperiodexpr
alltxnspans :: [DateSpan]
alltxnspans = Bool -> Interval -> DateSpan -> [DateSpan]
splitSpan Bool
adjust Interval
ptinterval DateSpan
span'
where
span' :: DateSpan
span' = DateSpan
ptspan DateSpan -> DateSpan -> DateSpan
`spanDefaultsFrom` DateSpan
requestedspan
adjust :: Bool
adjust = Maybe Day -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Day -> Bool) -> Maybe Day -> Bool
forall a b. (a -> b) -> a -> b
$ DateSpan -> Maybe Day
spanStart DateSpan
span'
checkPeriodicTransactionStartDate :: Interval -> DateSpan -> T.Text -> Maybe String
checkPeriodicTransactionStartDate :: Interval -> DateSpan -> AccountName -> Maybe [Char]
checkPeriodicTransactionStartDate Interval
i DateSpan
s AccountName
periodexpr =
case (Interval
i, DateSpan -> Maybe Day
spanStart DateSpan
s) of
(Weeks Int
_, Just Day
d) -> Day -> SmartInterval -> Maybe [Char]
checkStart Day
d SmartInterval
Week
(Months Int
_, Just Day
d) -> Day -> SmartInterval -> Maybe [Char]
checkStart Day
d SmartInterval
Month
(Quarters Int
_, Just Day
d) -> Day -> SmartInterval -> Maybe [Char]
checkStart Day
d SmartInterval
Quarter
(Years Int
_, Just Day
d) -> Day -> SmartInterval -> Maybe [Char]
checkStart Day
d SmartInterval
Year
(Interval, Maybe Day)
_ -> Maybe [Char]
forall a. Maybe a
Nothing
where
checkStart :: Day -> SmartInterval -> Maybe [Char]
checkStart Day
d SmartInterval
x =
let firstDate :: Day
firstDate = EFDay -> Day
fromEFDay (EFDay -> Day) -> EFDay -> Day
forall a b. (a -> b) -> a -> b
$ Day -> SmartDate -> EFDay
fixSmartDate Day
d (SmartDate -> EFDay) -> SmartDate -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> SmartInterval -> SmartDate
SmartRelative Integer
0 SmartInterval
x
in
if Day
d Day -> Day -> Bool
forall a. Eq a => a -> a -> Bool
== Day
firstDate
then Maybe [Char]
forall a. Maybe a
Nothing
else [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just ([Char] -> Maybe [Char]) -> [Char] -> Maybe [Char]
forall a b. (a -> b) -> a -> b
$
[Char]
"Unable to generate transactions according to "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ShowS
forall a. Show a => a -> [Char]
show (AccountName -> [Char]
T.unpack AccountName
periodexpr)
[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
" because "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Day -> [Char]
forall a. Show a => a -> [Char]
show Day
d[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
" is not a first day of the "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++SmartInterval -> [Char]
forall a. Show a => a -> [Char]
show SmartInterval
x