instead of a list of Amounts. No longer export Mixed constructor, to keep API clean (if you really need it, you can import it directly from Hledger.Data.Types). We also ensure the JSON representation of MixedAmount doesn't change: it is stored as a normalised list of Amounts. This commit improves performance. Here are some indicative results. hledger reg -f examples/10000x1000x10.journal - Maximum residency decreases from 65MB to 60MB (8% decrease) - Total memory in use decreases from 178MiB to 157MiB (12% decrease) hledger reg -f examples/10000x10000x10.journal - Maximum residency decreases from 69MB to 60MB (13% decrease) - Total memory in use decreases from 198MiB to 153MiB (23% decrease) hledger bal -f examples/10000x1000x10.journal - Total heap usage decreases from 6.4GB to 6.0GB (6% decrease) - Total memory in use decreases from 178MiB to 153MiB (14% decrease) hledger bal -f examples/10000x10000x10.journal - Total heap usage decreases from 7.3GB to 6.9GB (5% decrease) - Total memory in use decreases from 196MiB to 185MiB (5% decrease) hledger bal -M -f examples/10000x1000x10.journal - Total heap usage decreases from 16.8GB to 10.6GB (47% decrease) - Total time decreases from 14.3s to 12.0s (16% decrease) hledger bal -M -f examples/10000x10000x10.journal - Total heap usage decreases from 108GB to 48GB (56% decrease) - Total time decreases from 62s to 41s (33% decrease) If you never directly use the constructor Mixed or pattern match against it then you don't need to make any changes. If you do, then do the following: - If you really care about the individual Amounts and never normalise your MixedAmount (for example, just storing `Mixed amts` and then extracting `amts` as a pattern match, then use should switch to using [Amount]. This should just involve removing the `Mixed` constructor. - If you ever call `mixed`, `normaliseMixedAmount`, or do any sort of amount arithmetic (+), (-), then you should replace the constructor `Mixed` with the function `mixed`. To extract the list of Amounts, use the function `amounts`. - If you ever call `normaliseMixedAmountSquashPricesForDisplay`, you can replace that with `mixedAmountStripPrices`. (N.B. this does something slightly different from `normaliseMixedAmountSquashPricesForDisplay`, but I don't think there's any use case for squashing prices and then keeping the first of the squashed prices around. If you disagree let me know.) - Any remaining calls to `normaliseMixedAmount` can be removed, as that is now the identity function.
		
			
				
	
	
		
			260 lines
		
	
	
		
			7.3 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			260 lines
		
	
	
		
			7.3 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| --- * -*- outline-regexp:"--- \\*"; -*-
 | |
| --- ** doc
 | |
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections.
 | |
| {-|
 | |
| 
 | |
| A reader for the "timedot" file format.
 | |
| Example:
 | |
| 
 | |
| @
 | |
| #DATE
 | |
| #ACCT  DOTS  # Each dot represents 15m, spaces are ignored
 | |
| #ACCT  8    # numbers with or without a following h represent hours
 | |
| #ACCT  5m   # numbers followed by m represent minutes
 | |
| 
 | |
| # on 2/1, 1h was spent on FOSS haskell work, 0.25h on research, etc.
 | |
| 2/1
 | |
| fos.haskell   .... ..
 | |
| biz.research  .
 | |
| inc.client1   .... .... .... .... .... ....
 | |
| 
 | |
| 2/2
 | |
| biz.research  .
 | |
| inc.client1   .... .... ..
 | |
| 
 | |
| @
 | |
| 
 | |
| -}
 | |
| 
 | |
| --- ** language
 | |
| {-# LANGUAGE OverloadedStrings #-}
 | |
| {-# LANGUAGE PackageImports #-}
 | |
| 
 | |
| --- ** exports
 | |
| module Hledger.Read.TimedotReader (
 | |
|   -- * Reader
 | |
|   reader,
 | |
|   -- * Misc other exports
 | |
|   timedotfilep,
 | |
| )
 | |
| where
 | |
| 
 | |
| --- ** imports
 | |
| import Prelude ()
 | |
| import "base-compat-batteries" Prelude.Compat
 | |
| import Control.Monad
 | |
| import Control.Monad.Except (ExceptT)
 | |
| import Control.Monad.State.Strict
 | |
| import Data.Char (isSpace)
 | |
| import Data.List (foldl')
 | |
| import Data.Text (Text)
 | |
| import qualified Data.Text as T
 | |
| import Data.Time (Day)
 | |
| import Text.Megaparsec hiding (parse)
 | |
| import Text.Megaparsec.Char
 | |
| 
 | |
| import Hledger.Data
 | |
| import Hledger.Read.Common hiding (emptyorcommentlinep)
 | |
| import Hledger.Utils
 | |
| 
 | |
| --- ** doctest setup
 | |
| -- $setup
 | |
| -- >>> :set -XOverloadedStrings
 | |
| 
 | |
| --- ** reader
 | |
| 
 | |
| reader :: MonadIO m => Reader m
 | |
| reader = Reader
 | |
|   {rFormat     = "timedot"
 | |
|   ,rExtensions = ["timedot"]
 | |
|   ,rReadFn     = parse
 | |
|   ,rParser    = timedotp
 | |
|   }
 | |
| 
 | |
| -- | Parse and post-process a "Journal" from the timedot format, or give an error.
 | |
| parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal
 | |
| parse = parseAndFinaliseJournal' timedotp
 | |
| 
 | |
| --- ** utilities
 | |
| 
 | |
| traceparse, traceparse' :: String -> TextParser m ()
 | |
| traceparse  = const $ return ()
 | |
| traceparse' = const $ return ()
 | |
| -- for debugging:
 | |
| -- traceparse  s = traceParse (s++"?")
 | |
| -- traceparse' s = trace s $ return ()
 | |
| 
 | |
| --- ** parsers
 | |
| {-
 | |
| Rough grammar for timedot format:
 | |
| 
 | |
| timedot:           preamble day*
 | |
| preamble:          (emptyline | commentline | orgheading)*
 | |
| orgheading:        orgheadingprefix restofline
 | |
| day:               dateline entry* (emptyline | commentline)*
 | |
| dateline:          orgheadingprefix? date description?
 | |
| orgheadingprefix:  star+ space+
 | |
| description:       restofline  ; till semicolon?
 | |
| entry:          orgheadingprefix? space* singlespaced (doublespace quantity?)?
 | |
| doublespace:       space space+
 | |
| quantity:          (dot (dot | space)* | number | number unit)
 | |
| 
 | |
| Date lines and item lines can begin with an org heading prefix, which is ignored.
 | |
| Org headings before the first date line are ignored, regardless of content.
 | |
| -}
 | |
| 
 | |
| timedotfilep = timedotp -- XXX rename export above
 | |
| 
 | |
| timedotp :: JournalParser m ParsedJournal
 | |
| timedotp = preamblep >> many dayp >> eof >> get
 | |
| 
 | |
| preamblep :: JournalParser m ()
 | |
| preamblep = do
 | |
|   lift $ traceparse "preamblep"
 | |
|   many $ notFollowedBy datelinep >> (lift $ emptyorcommentlinep "#;*")
 | |
|   lift $ traceparse' "preamblep"
 | |
| 
 | |
| -- | Parse timedot day entries to zero or more time transactions for that day.
 | |
| -- @
 | |
| -- 2020/2/1 optional day description
 | |
| -- fos.haskell  .... ..
 | |
| -- biz.research .
 | |
| -- inc.client1  .... .... .... .... .... ....
 | |
| -- @
 | |
| dayp :: JournalParser m ()
 | |
| dayp = label "timedot day entry" $ do
 | |
|   lift $ traceparse "dayp"
 | |
|   (d,desc) <- datelinep
 | |
|   commentlinesp
 | |
|   ts <- many $ entryp <* commentlinesp
 | |
|   modify' $ addTransactions $ map (\t -> t{tdate=d, tdescription=desc}) ts
 | |
|   lift $ traceparse' "dayp"
 | |
|   where
 | |
|     addTransactions :: [Transaction] -> Journal -> Journal
 | |
|     addTransactions ts j = foldl' (flip ($)) j (map addTransaction ts)
 | |
| 
 | |
| datelinep :: JournalParser m (Day,Text)
 | |
| datelinep = do
 | |
|   lift $ traceparse "datelinep"
 | |
|   lift $ optional orgheadingprefixp
 | |
|   d <- datep
 | |
|   desc <- strip <$> lift restofline
 | |
|   lift $ traceparse' "datelinep"
 | |
|   return (d, T.pack desc)
 | |
| 
 | |
| -- | Zero or more empty lines or hash/semicolon comment lines
 | |
| -- or org headlines which do not start a new day.
 | |
| commentlinesp :: JournalParser m ()
 | |
| commentlinesp = do
 | |
|   lift $ traceparse "commentlinesp"
 | |
|   void $ many $ try $ lift $ emptyorcommentlinep "#;"
 | |
| 
 | |
| -- orgnondatelinep :: JournalParser m ()
 | |
| -- orgnondatelinep = do
 | |
| --   lift $ traceparse "orgnondatelinep"
 | |
| --   lift orgheadingprefixp
 | |
| --   notFollowedBy datelinep
 | |
| --   void $ lift restofline
 | |
| --   lift $ traceparse' "orgnondatelinep"
 | |
| 
 | |
| orgheadingprefixp = do
 | |
|   -- traceparse "orgheadingprefixp"
 | |
|   skipSome (char '*') >> skipNonNewlineSpaces1
 | |
| 
 | |
| -- | Parse a single timedot entry to one (dateless) transaction.
 | |
| -- @
 | |
| -- fos.haskell  .... ..
 | |
| -- @
 | |
| entryp :: JournalParser m Transaction
 | |
| entryp = do
 | |
|   lift $ traceparse "entryp"
 | |
|   pos <- genericSourcePos <$> getSourcePos
 | |
|   notFollowedBy datelinep
 | |
|   lift $ optional $ choice [orgheadingprefixp, skipNonNewlineSpaces1]
 | |
|   a <- modifiedaccountnamep
 | |
|   lift skipNonNewlineSpaces
 | |
|   hours <-
 | |
|     try (lift followingcommentp >> return 0)
 | |
|     <|> (durationp <*
 | |
|          (try (lift followingcommentp) <|> (newline >> return "")))
 | |
|   let t = nulltransaction{
 | |
|         tsourcepos = pos,
 | |
|         tstatus    = Cleared,
 | |
|         tpostings  = [
 | |
|           nullposting{paccount=a
 | |
|                      ,pamount=mixedAmount . amountSetPrecision (Precision 2) $ num hours  -- don't assume hours; do set precision to 2
 | |
|                      ,ptype=VirtualPosting
 | |
|                      ,ptransaction=Just t
 | |
|                      }
 | |
|           ]
 | |
|         }
 | |
|   lift $ traceparse' "entryp"
 | |
|   return t
 | |
| 
 | |
| durationp :: JournalParser m Quantity
 | |
| durationp = do
 | |
|   lift $ traceparse "durationp"
 | |
|   try numericquantityp <|> dotquantityp
 | |
|     -- <* traceparse' "durationp"
 | |
| 
 | |
| -- | Parse a duration of seconds, minutes, hours, days, weeks, months or years,
 | |
| -- written as a decimal number followed by s, m, h, d, w, mo or y, assuming h
 | |
| -- if there is no unit. Returns the duration as hours, assuming
 | |
| -- 1m = 60s, 1h = 60m, 1d = 24h, 1w = 7d, 1mo = 30d, 1y=365d.
 | |
| -- @
 | |
| -- 1.5
 | |
| -- 1.5h
 | |
| -- 90m
 | |
| -- @
 | |
| numericquantityp :: JournalParser m Quantity
 | |
| numericquantityp = do
 | |
|   -- lift $ traceparse "numericquantityp"
 | |
|   (q, _, _, _) <- lift $ numberp Nothing
 | |
|   msymbol <- optional $ choice $ map (string . fst) timeUnits
 | |
|   lift skipNonNewlineSpaces
 | |
|   let q' =
 | |
|         case msymbol of
 | |
|           Nothing  -> q
 | |
|           Just sym ->
 | |
|             case lookup sym timeUnits of
 | |
|               Just mult -> q * mult
 | |
|               Nothing   -> q  -- shouldn't happen.. ignore
 | |
|   return q'
 | |
| 
 | |
| -- (symbol, equivalent in hours).
 | |
| timeUnits =
 | |
|   [("s",2.777777777777778e-4)
 | |
|   ,("mo",5040) -- before "m"
 | |
|   ,("m",1.6666666666666666e-2)
 | |
|   ,("h",1)
 | |
|   ,("d",24)
 | |
|   ,("w",168)
 | |
|   ,("y",61320)
 | |
|   ]
 | |
| 
 | |
| -- | Parse a quantity written as a line of dots, each representing 0.25.
 | |
| -- @
 | |
| -- .... ..
 | |
| -- @
 | |
| dotquantityp :: JournalParser m Quantity
 | |
| dotquantityp = do
 | |
|   -- lift $ traceparse "dotquantityp"
 | |
|   dots <- filter (not.isSpace) <$> many (oneOf (". " :: [Char]))
 | |
|   return $ fromIntegral (length dots) / 4
 | |
| 
 | |
| -- | XXX new comment line parser, move to Hledger.Read.Common.emptyorcommentlinep
 | |
| -- Parse empty lines, all-blank lines, and lines beginning with any of the provided
 | |
| -- comment-beginning characters.
 | |
| emptyorcommentlinep :: [Char] -> TextParser m ()
 | |
| emptyorcommentlinep cs =
 | |
|   label ("empty line or comment line beginning with "++cs) $ do
 | |
|     traceparse "emptyorcommentlinep" -- XXX possible to combine label and traceparse ?
 | |
|     skipNonNewlineSpaces
 | |
|     void newline <|> void commentp
 | |
|     traceparse' "emptyorcommentlinep"
 | |
|     where
 | |
|       commentp = do
 | |
|         choice (map (some.char) cs)
 | |
|         takeWhileP Nothing (/='\n') <* newline
 | |
| 
 |