;lib: fix org headings and doctest setup that were breaking haddock
(and in some cases, installation). [ci skip]
This commit is contained in:
		
							parent
							
								
									db877d7355
								
							
						
					
					
						commit
						374be00223
					
				| @ -1,5 +1,5 @@ | |||||||
| -- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"-- "; -*- | --- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"--- "; -*- | ||||||
| -- ** doc | --- ** doc | ||||||
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| @ -10,16 +10,12 @@ to import modules below this one. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| -- ** language | --- ** language | ||||||
| {-# LANGUAGE OverloadedStrings #-} | {-# LANGUAGE OverloadedStrings #-} | ||||||
| {-# LANGUAGE PackageImports #-} | {-# LANGUAGE PackageImports #-} | ||||||
| {-# LANGUAGE ScopedTypeVariables #-} | {-# LANGUAGE ScopedTypeVariables #-} | ||||||
| 
 | 
 | ||||||
| -- ** doctest setup | --- ** exports | ||||||
| -- $setup |  | ||||||
| -- >>> :set -XOverloadedStrings |  | ||||||
| 
 |  | ||||||
| -- ** exports |  | ||||||
| module Hledger.Read ( | module Hledger.Read ( | ||||||
| 
 | 
 | ||||||
|   -- * Journal files |   -- * Journal files | ||||||
| @ -47,7 +43,7 @@ module Hledger.Read ( | |||||||
| 
 | 
 | ||||||
| ) where | ) where | ||||||
| 
 | 
 | ||||||
| -- ** imports | --- ** imports | ||||||
| import Control.Arrow (right) | import Control.Arrow (right) | ||||||
| import qualified Control.Exception as C | import qualified Control.Exception as C | ||||||
| import Control.Monad (when) | import Control.Monad (when) | ||||||
| @ -78,14 +74,16 @@ import Hledger.Read.CsvReader (tests_CsvReader) | |||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| import Prelude hiding (getContents, writeFile) | import Prelude hiding (getContents, writeFile) | ||||||
| 
 | 
 | ||||||
| -- ** environment | --- ** doctest setup | ||||||
|  | -- $setup | ||||||
|  | -- >>> :set -XOverloadedStrings | ||||||
|  | 
 | ||||||
|  | --- ** journal reading | ||||||
| 
 | 
 | ||||||
| journalEnvVar           = "LEDGER_FILE" | journalEnvVar           = "LEDGER_FILE" | ||||||
| journalEnvVar2          = "LEDGER" | journalEnvVar2          = "LEDGER" | ||||||
| journalDefaultFilename  = ".hledger.journal" | journalDefaultFilename  = ".hledger.journal" | ||||||
| 
 | 
 | ||||||
| -- ** journal reading |  | ||||||
| 
 |  | ||||||
| -- | Read a Journal from the given text, assuming journal format; or | -- | Read a Journal from the given text, assuming journal format; or | ||||||
| -- throw an error. | -- throw an error. | ||||||
| readJournal' :: Text -> IO Journal | readJournal' :: Text -> IO Journal | ||||||
| @ -186,7 +184,7 @@ readJournalFile iopts prefixedfile = do | |||||||
|       return $ Right newj |       return $ Right newj | ||||||
|     Right j -> return $ Right j |     Right j -> return $ Right j | ||||||
| 
 | 
 | ||||||
| -- ** utilities | --- ** utilities | ||||||
| 
 | 
 | ||||||
| -- | If the specified journal file does not exist (and is not "-"), | -- | If the specified journal file does not exist (and is not "-"), | ||||||
| -- give a helpful error and quit. | -- give a helpful error and quit. | ||||||
| @ -285,7 +283,7 @@ journalFilterSinceLatestDates ds@(d:_) j = (j', ds') | |||||||
|     j'                    = j{jtxns=newsamedatets++laterts} |     j'                    = j{jtxns=newsamedatets++laterts} | ||||||
|     ds'                   = latestDates $ map tdate $ samedatets++laterts |     ds'                   = latestDates $ map tdate $ samedatets++laterts | ||||||
| 
 | 
 | ||||||
| -- ** tests | --- ** tests | ||||||
| 
 | 
 | ||||||
| tests_Read = tests "Read" [ | tests_Read = tests "Read" [ | ||||||
|    tests_Common |    tests_Common | ||||||
|  | |||||||
| @ -1,5 +1,5 @@ | |||||||
| -- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"-- "; -*- | --- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"--- "; -*- | ||||||
| -- ** doc | --- ** doc | ||||||
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| @ -11,7 +11,7 @@ Some of these might belong in Hledger.Read.JournalReader or Hledger.Read. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| -- ** language | --- ** language | ||||||
| {-# LANGUAGE BangPatterns #-} | {-# LANGUAGE BangPatterns #-} | ||||||
| {-# LANGUAGE CPP #-} | {-# LANGUAGE CPP #-} | ||||||
| {-# LANGUAGE DeriveDataTypeable #-} | {-# LANGUAGE DeriveDataTypeable #-} | ||||||
| @ -27,11 +27,7 @@ Some of these might belong in Hledger.Read.JournalReader or Hledger.Read. | |||||||
| {-# LANGUAGE TupleSections #-} | {-# LANGUAGE TupleSections #-} | ||||||
| {-# LANGUAGE TypeFamilies #-} | {-# LANGUAGE TypeFamilies #-} | ||||||
| 
 | 
 | ||||||
| -- ** doctest setup | --- ** exports | ||||||
| -- $setup |  | ||||||
| -- >>> :set -XOverloadedStrings |  | ||||||
| 
 |  | ||||||
| -- ** exports |  | ||||||
| module Hledger.Read.Common ( | module Hledger.Read.Common ( | ||||||
|   Reader (..), |   Reader (..), | ||||||
|   InputOpts (..), |   InputOpts (..), | ||||||
| @ -114,7 +110,7 @@ module Hledger.Read.Common ( | |||||||
| ) | ) | ||||||
| where | where | ||||||
| 
 | 
 | ||||||
| -- ** imports | --- ** imports | ||||||
| import Prelude () | import Prelude () | ||||||
| import "base-compat-batteries" Prelude.Compat hiding (fail, readFile) | import "base-compat-batteries" Prelude.Compat hiding (fail, readFile) | ||||||
| import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail) | import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail) | ||||||
| @ -145,7 +141,11 @@ import Text.Megaparsec.Custom | |||||||
| import Hledger.Data | import Hledger.Data | ||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| 
 | 
 | ||||||
| -- ** types | --- ** doctest setup | ||||||
|  | -- $setup | ||||||
|  | -- >>> :set -XOverloadedStrings | ||||||
|  | 
 | ||||||
|  | --- ** types | ||||||
| 
 | 
 | ||||||
| -- main types; a few more below | -- main types; a few more below | ||||||
| 
 | 
 | ||||||
| @ -210,7 +210,7 @@ rawOptsToInputOpts rawopts = InputOpts{ | |||||||
|   ,auto_              = boolopt "auto" rawopts |   ,auto_              = boolopt "auto" rawopts | ||||||
|   } |   } | ||||||
| 
 | 
 | ||||||
| -- ** parsing utilities | --- ** parsing utilities | ||||||
| 
 | 
 | ||||||
| -- | Run a text parser in the identity monad. See also: parseWithState. | -- | Run a text parser in the identity monad. See also: parseWithState. | ||||||
| runTextParser, rtp | runTextParser, rtp | ||||||
| @ -401,8 +401,8 @@ match' p = do | |||||||
|   (!txt, p) <- match p |   (!txt, p) <- match p | ||||||
|   pure (txt, p) |   pure (txt, p) | ||||||
| 
 | 
 | ||||||
| -- ** parsers | --- ** parsers | ||||||
| -- *** transaction bits | --- *** transaction bits | ||||||
| 
 | 
 | ||||||
| statusp :: TextParser m Status | statusp :: TextParser m Status | ||||||
| statusp = | statusp = | ||||||
| @ -425,7 +425,7 @@ descriptionp :: TextParser m Text | |||||||
| descriptionp = takeWhileP Nothing (not . semicolonOrNewline) | descriptionp = takeWhileP Nothing (not . semicolonOrNewline) | ||||||
|   where semicolonOrNewline c = c == ';' || c == '\n' |   where semicolonOrNewline c = c == ';' || c == '\n' | ||||||
| 
 | 
 | ||||||
| -- *** dates | --- *** dates | ||||||
| 
 | 
 | ||||||
| -- | Parse a date in YYYY-MM-DD format. | -- | Parse a date in YYYY-MM-DD format. | ||||||
| -- Slash (/) and period (.) are also allowed as separators. | -- Slash (/) and period (.) are also allowed as separators. | ||||||
| @ -543,7 +543,7 @@ secondarydatep :: Day -> TextParser m Day | |||||||
| secondarydatep primaryDate = char '=' *> datep' (Just primaryYear) | secondarydatep primaryDate = char '=' *> datep' (Just primaryYear) | ||||||
|   where primaryYear = first3 $ toGregorian primaryDate |   where primaryYear = first3 $ toGregorian primaryDate | ||||||
| 
 | 
 | ||||||
| -- *** account names | --- *** account names | ||||||
| 
 | 
 | ||||||
| -- | Parse an account name (plus one following space if present), | -- | Parse an account name (plus one following space if present), | ||||||
| -- then apply any parent account prefix and/or account aliases currently in effect, | -- then apply any parent account prefix and/or account aliases currently in effect, | ||||||
| @ -592,7 +592,7 @@ singlespacedtextsatisfyingp pred = do | |||||||
| singlespacep :: TextParser m () | singlespacep :: TextParser m () | ||||||
| singlespacep = void spacenonewline *> notFollowedBy spacenonewline | singlespacep = void spacenonewline *> notFollowedBy spacenonewline | ||||||
| 
 | 
 | ||||||
| -- *** amounts | --- *** amounts | ||||||
| 
 | 
 | ||||||
| -- | Parse whitespace then an amount, with an optional left or right | -- | Parse whitespace then an amount, with an optional left or right | ||||||
| -- currency symbol and optional price, or return the special | -- currency symbol and optional price, or return the special | ||||||
| @ -995,7 +995,7 @@ digitgroupp = label "digits" | |||||||
|     makeGroup = uncurry DigitGrp . foldl' step (0, 0) . T.unpack |     makeGroup = uncurry DigitGrp . foldl' step (0, 0) . T.unpack | ||||||
|     step (!l, !a) c = (l+1, a*10 + fromIntegral (digitToInt c)) |     step (!l, !a) c = (l+1, a*10 + fromIntegral (digitToInt c)) | ||||||
| 
 | 
 | ||||||
| -- *** comments | --- *** comments | ||||||
| 
 | 
 | ||||||
| multilinecommentp :: TextParser m () | multilinecommentp :: TextParser m () | ||||||
| multilinecommentp = startComment *> anyLine `skipManyTill` endComment | multilinecommentp = startComment *> anyLine `skipManyTill` endComment | ||||||
| @ -1302,7 +1302,7 @@ bracketeddatetagsp mYear1 = do | |||||||
| 
 | 
 | ||||||
| {-# INLINABLE bracketeddatetagsp #-} | {-# INLINABLE bracketeddatetagsp #-} | ||||||
| 
 | 
 | ||||||
| -- ** tests | --- ** tests | ||||||
| 
 | 
 | ||||||
| tests_Common = tests "Common" [ | tests_Common = tests "Common" [ | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -1,5 +1,5 @@ | |||||||
| -- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"-- "; -*- | --- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"--- "; -*- | ||||||
| -- ** doc | --- ** doc | ||||||
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| @ -10,7 +10,7 @@ A reader for CSV data, using an extra rules file to help interpret the data. | |||||||
| -- Here's a command that will render them: | -- Here's a command that will render them: | ||||||
| -- stack haddock hledger-lib --fast --no-haddock-deps --haddock-arguments='--ignore-all-exports' --open | -- stack haddock hledger-lib --fast --no-haddock-deps --haddock-arguments='--ignore-all-exports' --open | ||||||
| 
 | 
 | ||||||
| -- ** language | --- ** language | ||||||
| {-# LANGUAGE CPP #-} | {-# LANGUAGE CPP #-} | ||||||
| {-# LANGUAGE FlexibleContexts #-} | {-# LANGUAGE FlexibleContexts #-} | ||||||
| {-# LANGUAGE FlexibleInstances #-} | {-# LANGUAGE FlexibleInstances #-} | ||||||
| @ -24,11 +24,7 @@ A reader for CSV data, using an extra rules file to help interpret the data. | |||||||
| {-# LANGUAGE TypeSynonymInstances #-} | {-# LANGUAGE TypeSynonymInstances #-} | ||||||
| {-# LANGUAGE ViewPatterns #-} | {-# LANGUAGE ViewPatterns #-} | ||||||
| 
 | 
 | ||||||
| -- ** doctest setup | --- ** exports | ||||||
| -- $setup |  | ||||||
| -- >>> :set -XOverloadedStrings |  | ||||||
| 
 |  | ||||||
| -- ** exports |  | ||||||
| module Hledger.Read.CsvReader ( | module Hledger.Read.CsvReader ( | ||||||
|   -- * Reader |   -- * Reader | ||||||
|   reader, |   reader, | ||||||
| @ -43,7 +39,7 @@ module Hledger.Read.CsvReader ( | |||||||
| ) | ) | ||||||
| where | where | ||||||
| 
 | 
 | ||||||
| -- ** imports | --- ** imports | ||||||
| import Prelude () | import Prelude () | ||||||
| import "base-compat-batteries" Prelude.Compat hiding (fail) | import "base-compat-batteries" Prelude.Compat hiding (fail) | ||||||
| import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail) | import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail) | ||||||
| @ -87,13 +83,17 @@ import Hledger.Data | |||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| import Hledger.Read.Common (Reader(..),InputOpts(..),amountp, statusp, genericSourcePos, finaliseJournal) | import Hledger.Read.Common (Reader(..),InputOpts(..),amountp, statusp, genericSourcePos, finaliseJournal) | ||||||
| 
 | 
 | ||||||
| -- ** some types | --- ** doctest setup | ||||||
|  | -- $setup | ||||||
|  | -- >>> :set -XOverloadedStrings | ||||||
|  | 
 | ||||||
|  | --- ** some types | ||||||
| 
 | 
 | ||||||
| type CSV       = [CsvRecord] | type CSV       = [CsvRecord] | ||||||
| type CsvRecord = [CsvValue] | type CsvRecord = [CsvValue] | ||||||
| type CsvValue  = String | type CsvValue  = String | ||||||
| 
 | 
 | ||||||
| -- ** reader | --- ** reader | ||||||
| 
 | 
 | ||||||
| reader :: MonadIO m => Reader m | reader :: MonadIO m => Reader m | ||||||
| reader = Reader | reader = Reader | ||||||
| @ -119,8 +119,8 @@ parse iopts f t = do | |||||||
|                 -- better preemptively reverse them once more. XXX inefficient |                 -- better preemptively reverse them once more. XXX inefficient | ||||||
|                 pj' = journalReverse pj |                 pj' = journalReverse pj | ||||||
| 
 | 
 | ||||||
| -- ** reading rules files | --- ** reading rules files | ||||||
| -- *** rules utilities | --- *** rules utilities | ||||||
| 
 | 
 | ||||||
| -- Not used by hledger; just for lib users,  | -- Not used by hledger; just for lib users,  | ||||||
| -- | An pure-exception-throwing IO action that parses this file's content | -- | An pure-exception-throwing IO action that parses this file's content | ||||||
| @ -232,7 +232,7 @@ validateRules rules = do | |||||||
|   where |   where | ||||||
|     isAssigned f = isJust $ getEffectiveAssignment rules [] f |     isAssigned f = isJust $ getEffectiveAssignment rules [] f | ||||||
| 
 | 
 | ||||||
| -- *** rules types | --- *** rules types | ||||||
| 
 | 
 | ||||||
| -- | A set of data definitions and account-matching patterns sufficient to | -- | A set of data definitions and account-matching patterns sufficient to | ||||||
| -- convert a particular CSV data file into meaningful journal transactions. | -- convert a particular CSV data file into meaningful journal transactions. | ||||||
| @ -300,7 +300,7 @@ defrules = CsvRules { | |||||||
|   rconditionalblocks=[] |   rconditionalblocks=[] | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| -- *** rules parsers | --- *** rules parsers | ||||||
| 
 | 
 | ||||||
| {- | {- | ||||||
| Grammar for the CSV conversion rules, more or less: | Grammar for the CSV conversion rules, more or less: | ||||||
| @ -573,7 +573,7 @@ regexp = do | |||||||
| --   -- ,"!=" | --   -- ,"!=" | ||||||
| --   ] | --   ] | ||||||
| 
 | 
 | ||||||
| -- ** reading csv files | --- ** reading csv files | ||||||
| 
 | 
 | ||||||
| -- | Read a Journal from the given CSV data (and filename, used for error | -- | Read a Journal from the given CSV data (and filename, used for error | ||||||
| -- messages), or return an error. Proceed as follows: | -- messages), or return an error. Proceed as follows: | ||||||
| @ -748,7 +748,7 @@ validateCsv rules numhdrlines (Right rs) = validate $ applyConditionalSkips $ dr | |||||||
| --                   ,date2Field r | --                   ,date2Field r | ||||||
| --                   ] | --                   ] | ||||||
| 
 | 
 | ||||||
| -- ** converting csv records to transactions | --- ** converting csv records to transactions | ||||||
| 
 | 
 | ||||||
| showRules rules record = | showRules rules record = | ||||||
|   unlines $ catMaybes [ (("the "++fld++" rule is: ")++) <$> getEffectiveAssignment rules record fld | fld <- journalfieldnames] |   unlines $ catMaybes [ (("the "++fld++" rule is: ")++) <$> getEffectiveAssignment rules record fld | fld <- journalfieldnames] | ||||||
| @ -1174,7 +1174,7 @@ parseDateWithCustomOrDefaultFormats mformat s = firstJust $ map parsewith format | |||||||
|                (:[]) |                (:[]) | ||||||
|                 mformat |                 mformat | ||||||
| 
 | 
 | ||||||
| -- ** tests | --- ** tests | ||||||
| 
 | 
 | ||||||
| tests_CsvReader = tests "CsvReader" [ | tests_CsvReader = tests "CsvReader" [ | ||||||
|    tests "parseCsvRules" [ |    tests "parseCsvRules" [ | ||||||
|  | |||||||
| @ -1,5 +1,5 @@ | |||||||
| -- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"-- "; -*- | --- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"--- "; -*- | ||||||
| -- ** doc | --- ** doc | ||||||
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| @ -24,7 +24,7 @@ Hledger.Read.Common, to avoid import cycles. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| -- ** language | --- ** language | ||||||
| 
 | 
 | ||||||
| {-# LANGUAGE CPP #-} | {-# LANGUAGE CPP #-} | ||||||
| {-# LANGUAGE FlexibleContexts #-} | {-# LANGUAGE FlexibleContexts #-} | ||||||
| @ -36,11 +36,7 @@ Hledger.Read.Common, to avoid import cycles. | |||||||
| {-# LANGUAGE ScopedTypeVariables #-} | {-# LANGUAGE ScopedTypeVariables #-} | ||||||
| {-# LANGUAGE TupleSections #-} | {-# LANGUAGE TupleSections #-} | ||||||
| 
 | 
 | ||||||
| -- ** doctest setup | --- ** exports | ||||||
| -- $setup |  | ||||||
| -- >>> :set -XOverloadedStrings |  | ||||||
| 
 |  | ||||||
| -- ** exports |  | ||||||
| module Hledger.Read.JournalReader ( | module Hledger.Read.JournalReader ( | ||||||
| 
 | 
 | ||||||
|   -- * Reader-finding utils |   -- * Reader-finding utils | ||||||
| @ -76,7 +72,7 @@ module Hledger.Read.JournalReader ( | |||||||
| ) | ) | ||||||
| where | where | ||||||
| 
 | 
 | ||||||
| -- ** imports | --- ** imports | ||||||
| -- import qualified Prelude (fail) | -- import qualified Prelude (fail) | ||||||
| -- import "base-compat-batteries" Prelude.Compat hiding (fail, readFile) | -- import "base-compat-batteries" Prelude.Compat hiding (fail, readFile) | ||||||
| import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail) | import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail) | ||||||
| @ -113,7 +109,11 @@ import qualified Hledger.Read.TimedotReader as TimedotReader (reader) | |||||||
| import qualified Hledger.Read.TimeclockReader as TimeclockReader (reader) | import qualified Hledger.Read.TimeclockReader as TimeclockReader (reader) | ||||||
| import qualified Hledger.Read.CsvReader as CsvReader (reader) | import qualified Hledger.Read.CsvReader as CsvReader (reader) | ||||||
| 
 | 
 | ||||||
| -- ** reader finding utilities | --- ** doctest setup | ||||||
|  | -- $setup | ||||||
|  | -- >>> :set -XOverloadedStrings | ||||||
|  | 
 | ||||||
|  | --- ** reader finding utilities | ||||||
| -- Defined here rather than Hledger.Read so that we can use them in includedirectivep below. | -- Defined here rather than Hledger.Read so that we can use them in includedirectivep below. | ||||||
| 
 | 
 | ||||||
| -- The available journal readers, each one handling a particular data format. | -- The available journal readers, each one handling a particular data format. | ||||||
| @ -156,7 +156,7 @@ splitReaderPrefix f = | |||||||
|   headDef (Nothing, f) |   headDef (Nothing, f) | ||||||
|   [(Just r, drop (length r + 1) f) | r <- readerNames, (r++":") `isPrefixOf` f] |   [(Just r, drop (length r + 1) f) | r <- readerNames, (r++":") `isPrefixOf` f] | ||||||
| 
 | 
 | ||||||
| -- ** reader | --- ** reader | ||||||
| 
 | 
 | ||||||
| reader :: MonadIO m => Reader m | reader :: MonadIO m => Reader m | ||||||
| reader = Reader | reader = Reader | ||||||
| @ -182,8 +182,8 @@ aliasesFromOpts :: InputOpts -> [AccountAlias] | |||||||
| aliasesFromOpts = map (\a -> fromparse $ runParser accountaliasp ("--alias "++quoteIfNeeded a) $ T.pack a) | aliasesFromOpts = map (\a -> fromparse $ runParser accountaliasp ("--alias "++quoteIfNeeded a) $ T.pack a) | ||||||
|                   . aliases_ |                   . aliases_ | ||||||
| 
 | 
 | ||||||
| -- ** parsers | --- ** parsers | ||||||
| -- *** journal | --- *** journal | ||||||
| 
 | 
 | ||||||
| -- | A journal parser. Accumulates and returns a "ParsedJournal", | -- | A journal parser. Accumulates and returns a "ParsedJournal", | ||||||
| -- which should be finalised/validated before use. | -- which should be finalised/validated before use. | ||||||
| @ -213,7 +213,7 @@ addJournalItemP = | |||||||
|     , void (lift multilinecommentp) |     , void (lift multilinecommentp) | ||||||
|     ] <?> "transaction or directive" |     ] <?> "transaction or directive" | ||||||
| 
 | 
 | ||||||
| -- *** directives | --- *** directives | ||||||
| 
 | 
 | ||||||
| -- | Parse any journal directive and update the parse state accordingly. | -- | Parse any journal directive and update the parse state accordingly. | ||||||
| -- Cf http://hledger.org/manual.html#directives, | -- Cf http://hledger.org/manual.html#directives, | ||||||
| @ -583,7 +583,7 @@ commodityconversiondirectivep = do | |||||||
|   lift restofline |   lift restofline | ||||||
|   return () |   return () | ||||||
| 
 | 
 | ||||||
| -- *** transactions | --- *** transactions | ||||||
| 
 | 
 | ||||||
| -- | Parse a transaction modifier (auto postings) rule. | -- | Parse a transaction modifier (auto postings) rule. | ||||||
| transactionmodifierp :: JournalParser m TransactionModifier | transactionmodifierp :: JournalParser m TransactionModifier | ||||||
| @ -680,7 +680,7 @@ transactionp = do | |||||||
|   let sourcepos = journalSourcePos startpos endpos |   let sourcepos = journalSourcePos startpos endpos | ||||||
|   return $ txnTieKnot $ Transaction 0 "" sourcepos date edate status code description comment tags postings |   return $ txnTieKnot $ Transaction 0 "" sourcepos date edate status code description comment tags postings | ||||||
| 
 | 
 | ||||||
| -- *** postings | --- *** postings | ||||||
| 
 | 
 | ||||||
| -- Parse the following whitespace-beginning lines as postings, posting | -- Parse the following whitespace-beginning lines as postings, posting | ||||||
| -- tags, and/or comments (inferring year, if needed, from the given date). | -- tags, and/or comments (inferring year, if needed, from the given date). | ||||||
| @ -723,7 +723,7 @@ postingp mTransactionYear = do | |||||||
|    , pbalanceassertion=massertion |    , pbalanceassertion=massertion | ||||||
|    } |    } | ||||||
| 
 | 
 | ||||||
| -- ** tests | --- ** tests | ||||||
| 
 | 
 | ||||||
| tests_JournalReader = tests "JournalReader" [ | tests_JournalReader = tests "JournalReader" [ | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -1,5 +1,5 @@ | |||||||
| -- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"-- "; -*- | --- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"--- "; -*- | ||||||
| -- ** doc | --- ** doc | ||||||
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| @ -43,15 +43,11 @@ i, o or O.  The meanings of the codes are: | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| -- ** language | --- ** language | ||||||
| {-# LANGUAGE OverloadedStrings #-} | {-# LANGUAGE OverloadedStrings #-} | ||||||
| {-# LANGUAGE PackageImports #-} | {-# LANGUAGE PackageImports #-} | ||||||
| 
 | 
 | ||||||
| -- ** doctest setup | --- ** exports | ||||||
| -- $setup |  | ||||||
| -- >>> :set -XOverloadedStrings |  | ||||||
| 
 |  | ||||||
| -- ** exports |  | ||||||
| module Hledger.Read.TimeclockReader ( | module Hledger.Read.TimeclockReader ( | ||||||
|   -- * Reader |   -- * Reader | ||||||
|   reader, |   reader, | ||||||
| @ -60,7 +56,7 @@ module Hledger.Read.TimeclockReader ( | |||||||
| ) | ) | ||||||
| where | where | ||||||
| 
 | 
 | ||||||
| -- ** imports | --- ** imports | ||||||
| import           Prelude () | import           Prelude () | ||||||
| import "base-compat-batteries" Prelude.Compat | import "base-compat-batteries" Prelude.Compat | ||||||
| import           Control.Monad | import           Control.Monad | ||||||
| @ -76,7 +72,11 @@ import           Hledger.Data | |||||||
| import           Hledger.Read.Common | import           Hledger.Read.Common | ||||||
| import           Hledger.Utils | import           Hledger.Utils | ||||||
| 
 | 
 | ||||||
| -- ** reader | --- ** doctest setup | ||||||
|  | -- $setup | ||||||
|  | -- >>> :set -XOverloadedStrings | ||||||
|  | 
 | ||||||
|  | --- ** reader | ||||||
| 
 | 
 | ||||||
| reader :: MonadIO m => Reader m | reader :: MonadIO m => Reader m | ||||||
| reader = Reader | reader = Reader | ||||||
| @ -92,7 +92,7 @@ reader = Reader | |||||||
| parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal | parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal | ||||||
| parse = parseAndFinaliseJournal' timeclockfilep | parse = parseAndFinaliseJournal' timeclockfilep | ||||||
| 
 | 
 | ||||||
| -- ** parsers | --- ** parsers | ||||||
| 
 | 
 | ||||||
| timeclockfilep :: MonadIO m => JournalParser m ParsedJournal | timeclockfilep :: MonadIO m => JournalParser m ParsedJournal | ||||||
| timeclockfilep = do many timeclockitemp | timeclockfilep = do many timeclockitemp | ||||||
|  | |||||||
| @ -1,5 +1,5 @@ | |||||||
| -- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"-- "; -*- | --- * -*- eval: (orgstruct-mode 1); orgstruct-heading-prefix-regexp:"--- "; -*- | ||||||
| -- ** doc | --- ** doc | ||||||
| -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | -- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections. | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| @ -26,15 +26,11 @@ inc.client1   .... .... .. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| -- ** language | --- ** language | ||||||
| {-# LANGUAGE OverloadedStrings #-} | {-# LANGUAGE OverloadedStrings #-} | ||||||
| {-# LANGUAGE PackageImports #-} | {-# LANGUAGE PackageImports #-} | ||||||
| 
 | 
 | ||||||
| -- ** doctest setup | --- ** exports | ||||||
| -- $setup |  | ||||||
| -- >>> :set -XOverloadedStrings |  | ||||||
| 
 |  | ||||||
| -- ** exports |  | ||||||
| module Hledger.Read.TimedotReader ( | module Hledger.Read.TimedotReader ( | ||||||
|   -- * Reader |   -- * Reader | ||||||
|   reader, |   reader, | ||||||
| @ -43,7 +39,7 @@ module Hledger.Read.TimedotReader ( | |||||||
| ) | ) | ||||||
| where | where | ||||||
| 
 | 
 | ||||||
| -- ** imports | --- ** imports | ||||||
| import Prelude () | import Prelude () | ||||||
| import "base-compat-batteries" Prelude.Compat | import "base-compat-batteries" Prelude.Compat | ||||||
| import Control.Monad | import Control.Monad | ||||||
| @ -61,7 +57,11 @@ import Hledger.Data | |||||||
| import Hledger.Read.Common hiding (emptyorcommentlinep) | import Hledger.Read.Common hiding (emptyorcommentlinep) | ||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| 
 | 
 | ||||||
| -- ** reader | --- ** doctest setup | ||||||
|  | -- $setup | ||||||
|  | -- >>> :set -XOverloadedStrings | ||||||
|  | 
 | ||||||
|  | --- ** reader | ||||||
| 
 | 
 | ||||||
| reader :: MonadIO m => Reader m | reader :: MonadIO m => Reader m | ||||||
| reader = Reader | reader = Reader | ||||||
| @ -75,7 +75,7 @@ reader = Reader | |||||||
| parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal | parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal | ||||||
| parse = parseAndFinaliseJournal' timedotp | parse = parseAndFinaliseJournal' timedotp | ||||||
| 
 | 
 | ||||||
| -- ** utilities | --- ** utilities | ||||||
| 
 | 
 | ||||||
| traceparse, traceparse' :: String -> TextParser m () | traceparse, traceparse' :: String -> TextParser m () | ||||||
| traceparse  = const $ return () | traceparse  = const $ return () | ||||||
| @ -84,7 +84,7 @@ traceparse' = const $ return () | |||||||
| -- traceparse  s = traceParse (s++"?") | -- traceparse  s = traceParse (s++"?") | ||||||
| -- traceparse' s = trace s $ return () | -- traceparse' s = trace s $ return () | ||||||
| 
 | 
 | ||||||
| -- ** parsers | --- ** parsers | ||||||
| {- | {- | ||||||
| Rough grammar for timedot format: | Rough grammar for timedot format: | ||||||
| 
 | 
 | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user