mirror of
https://github.com/simonmichael/hledger.git
synced 2025-01-04 00:07:29 +03:00
dev: lens: Introduce lenses for InputOpts and BalancingOpts.
This commit is contained in:
parent
c784da3d0c
commit
435ec992f9
@ -9,11 +9,12 @@ tags.
|
||||
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE Rank2Types #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
module Hledger.Data.Transaction (
|
||||
-- * Transaction
|
||||
nulltransaction,
|
||||
@ -30,6 +31,7 @@ module Hledger.Data.Transaction (
|
||||
balancedVirtualPostings,
|
||||
transactionsPostings,
|
||||
BalancingOpts(..),
|
||||
HasBalancingOpts(..),
|
||||
defbalancingopts,
|
||||
isTransactionBalanced,
|
||||
balanceTransaction,
|
||||
@ -660,6 +662,10 @@ transactionFile Transaction{tsourcepos} =
|
||||
GenericSourcePos f _ _ -> f
|
||||
JournalSourcePos f _ -> f
|
||||
|
||||
-- lenses
|
||||
|
||||
makeHledgerClassyLenses ''BalancingOpts
|
||||
|
||||
-- tests
|
||||
|
||||
tests_Transaction :: TestTree
|
||||
|
@ -30,6 +30,7 @@ Some of these might belong in Hledger.Read.JournalReader or Hledger.Read.
|
||||
module Hledger.Read.Common (
|
||||
Reader (..),
|
||||
InputOpts(..),
|
||||
HasInputOpts(..),
|
||||
definputopts,
|
||||
rawOptsToInputOpts,
|
||||
rawOptsToCommodityStylesOpts,
|
||||
|
@ -4,10 +4,12 @@ Various options to use when reading journal files.
|
||||
Similar to CliOptions.inputflags, simplifies the journal-reading functions.
|
||||
|
||||
-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Hledger.Read.InputOptions (
|
||||
-- * Types and helpers for input options
|
||||
InputOpts(..)
|
||||
, HasInputOpts(..)
|
||||
, definputopts
|
||||
, forecastPeriod
|
||||
) where
|
||||
@ -16,10 +18,10 @@ import Control.Applicative ((<|>))
|
||||
import Data.Time (Day, addDays)
|
||||
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Transaction (BalancingOpts(..), defbalancingopts)
|
||||
import Hledger.Data.Transaction (BalancingOpts(..), HasBalancingOpts(..), defbalancingopts)
|
||||
import Hledger.Data.Journal (journalEndDate)
|
||||
import Hledger.Data.Dates (nulldatespan)
|
||||
import Hledger.Utils
|
||||
import Hledger.Utils (dbg2, makeHledgerClassyLenses)
|
||||
|
||||
data InputOpts = InputOpts {
|
||||
-- files_ :: [FilePath]
|
||||
@ -73,3 +75,10 @@ forecastPeriod d iopts j = do
|
||||
mjournalend = dbg2 "journalEndDate" $ journalEndDate False j -- ignore secondary dates
|
||||
DateSpan reportStart reportEnd = reportspan_ iopts
|
||||
return . dbg2 "forecastspan" $ DateSpan forecastStart forecastEnd
|
||||
|
||||
-- ** Lenses
|
||||
|
||||
makeHledgerClassyLenses ''InputOpts
|
||||
|
||||
instance HasBalancingOpts InputOpts where
|
||||
balancingOpts = balancingopts
|
||||
|
Loading…
Reference in New Issue
Block a user