lib: more verbose show instance for PeriodicTransaction
This commit is contained in:
		
							parent
							
								
									9076474a09
								
							
						
					
					
						commit
						43d973e8ab
					
				@ -1,6 +1,7 @@
 | 
			
		||||
{-# LANGUAGE CPP #-}
 | 
			
		||||
{-# LANGUAGE OverloadedStrings #-}
 | 
			
		||||
{-# LANGUAGE RecordWildCards #-}
 | 
			
		||||
{-# LANGUAGE CPP #-}
 | 
			
		||||
{-# LANGUAGE StandaloneDeriving #-}
 | 
			
		||||
{-|
 | 
			
		||||
 | 
			
		||||
A 'PeriodicTransaction' is a rule describing recurring transactions.
 | 
			
		||||
@ -16,6 +17,8 @@ where
 | 
			
		||||
import Data.Monoid ((<>))
 | 
			
		||||
#endif
 | 
			
		||||
import qualified Data.Text as T
 | 
			
		||||
import Text.Printf
 | 
			
		||||
 | 
			
		||||
import Hledger.Data.Types
 | 
			
		||||
import Hledger.Data.Dates
 | 
			
		||||
import Hledger.Data.Amount
 | 
			
		||||
@ -43,6 +46,27 @@ _ptgen str = do
 | 
			
		||||
          nullperiodictransaction{ ptperiodexpr=t , ptspan=s, ptinterval=i, ptpostings=["a" `post` usd 1] } 
 | 
			
		||||
          nulldatespan
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
--deriving instance Show PeriodicTransaction
 | 
			
		||||
-- for better pretty-printing:
 | 
			
		||||
instance Show PeriodicTransaction where
 | 
			
		||||
  show PeriodicTransaction{..} =
 | 
			
		||||
    printf "PeriodicTransactionPP {%s, %s, %s, %s, %s, %s, %s, %s, %s}"
 | 
			
		||||
      ("ptperiodexpr=" ++ show ptperiodexpr)
 | 
			
		||||
      ("ptinterval=" ++ show ptinterval)
 | 
			
		||||
      ("ptspan=" ++ show (show ptspan))
 | 
			
		||||
      ("ptstatus=" ++ show (show ptstatus))
 | 
			
		||||
      ("ptcode=" ++ show ptcode)
 | 
			
		||||
      ("ptdescription=" ++ show ptdescription)
 | 
			
		||||
      ("ptcomment=" ++ show ptcomment)
 | 
			
		||||
      ("pttags=" ++ show pttags)
 | 
			
		||||
      ("ptpostings=" ++ show ptpostings)
 | 
			
		||||
 | 
			
		||||
-- A basic human-readable rendering.
 | 
			
		||||
--showPeriodicTransaction t = "~ " ++ T.unpack (ptperiodexpr t) ++ "\n" ++ unlines (map show (ptpostings t))
 | 
			
		||||
 | 
			
		||||
--nullperiodictransaction is defined in Types.hs
 | 
			
		||||
 | 
			
		||||
-- | Generate transactions from 'PeriodicTransaction' within a 'DateSpan'
 | 
			
		||||
--
 | 
			
		||||
-- Note that new transactions require 'txnTieKnot' post-processing.
 | 
			
		||||
 | 
			
		||||
@ -68,9 +68,6 @@ instance Show Transaction where show = showTransactionUnelided
 | 
			
		||||
instance Show TransactionModifier where
 | 
			
		||||
    show t = "= " ++ T.unpack (tmquerytxt t) ++ "\n" ++ unlines (map show (tmpostings t))
 | 
			
		||||
 | 
			
		||||
instance Show PeriodicTransaction where
 | 
			
		||||
    show t = "~ " ++ T.unpack (ptperiodexpr t) ++ "\n" ++ unlines (map show (ptpostings t))
 | 
			
		||||
 | 
			
		||||
sourceFilePath :: GenericSourcePos -> FilePath
 | 
			
		||||
sourceFilePath = \case
 | 
			
		||||
    GenericSourcePos fp _ _ -> fp
 | 
			
		||||
 | 
			
		||||
@ -279,7 +279,7 @@ data PeriodicTransaction = PeriodicTransaction {
 | 
			
		||||
      ptcomment      :: Text,
 | 
			
		||||
      pttags         :: [Tag],
 | 
			
		||||
      ptpostings     :: [Posting]
 | 
			
		||||
    } deriving (Eq,Typeable,Data,Generic)
 | 
			
		||||
    } deriving (Eq,Typeable,Data,Generic) -- , Show in PeriodicTransaction.hs
 | 
			
		||||
 | 
			
		||||
nullperiodictransaction = PeriodicTransaction{
 | 
			
		||||
      ptperiodexpr   = ""
 | 
			
		||||
@ -313,7 +313,7 @@ data MarketPrice = MarketPrice {
 | 
			
		||||
      mpdate      :: Day,
 | 
			
		||||
      mpcommodity :: CommoditySymbol,
 | 
			
		||||
      mpamount    :: Amount
 | 
			
		||||
    } deriving (Eq,Ord,Typeable,Data,Generic) -- & Show (in Amount.hs)
 | 
			
		||||
    } deriving (Eq,Ord,Typeable,Data,Generic) -- , Show in Amount.hs
 | 
			
		||||
 | 
			
		||||
instance NFData MarketPrice
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		Loading…
	
		Reference in New Issue
	
	Block a user