refactor: more reader cleanups

This commit is contained in:
Simon Michael 2010-11-15 07:18:35 +00:00
parent a3a7a346ac
commit 17d5acf64b
5 changed files with 28 additions and 35 deletions

View File

@ -32,10 +32,12 @@ Evolution of transaction\/entry\/posting terminology:
module Hledger.Data.Types module Hledger.Data.Types
where where
import Hledger.Data.Utils import Control.Monad.Error (ErrorT)
import Data.Typeable (Typeable)
import qualified Data.Map as Map import qualified Data.Map as Map
import System.Time (ClockTime) import System.Time (ClockTime)
import Data.Typeable (Typeable)
import Hledger.Data.Utils
type SmartDate = (String,String,String) type SmartDate = (String,String,String)
@ -148,6 +150,17 @@ data Journal = Journal {
filereadtime :: ClockTime -- ^ when this journal was last read from its file(s) filereadtime :: ClockTime -- ^ when this journal was last read from its file(s)
} deriving (Eq, Typeable) } deriving (Eq, Typeable)
-- | A JournalUpdate is some transformation of a Journal. It can do I/O or
-- raise an error.
type JournalUpdate = ErrorT String IO (Journal -> Journal)
-- | A hledger journal reader is a triple of format name, format-detecting
-- predicate, and a parser to Journal.
data Reader = Reader {rFormat :: String
,rDetector :: FilePath -> String -> Bool
,rParser :: FilePath -> String -> ErrorT String IO Journal
}
data Ledger = Ledger { data Ledger = Ledger {
journal :: Journal, journal :: Journal,
accountnametree :: Tree AccountName, accountnametree :: Tree AccountName,

View File

@ -17,10 +17,9 @@ module Hledger.Read (
) )
where where
import Hledger.Data.Dates (getCurrentDay) import Hledger.Data.Dates (getCurrentDay)
import Hledger.Data.Types (Journal(..)) import Hledger.Data.Types (Journal(..), Reader(..))
import Hledger.Data.Journal (nullctx) import Hledger.Data.Journal (nullctx)
import Hledger.Data.Utils import Hledger.Data.Utils
import Hledger.Read.Common
import Hledger.Read.JournalReader as JournalReader import Hledger.Read.JournalReader as JournalReader
import Hledger.Read.TimelogReader as TimelogReader import Hledger.Read.TimelogReader as TimelogReader

View File

@ -124,16 +124,9 @@ import Text.ParserCombinators.Parsec hiding (parse)
import Prelude hiding (readFile, putStr, putStrLn, print, getContents) import Prelude hiding (readFile, putStr, putStrLn, print, getContents)
import System.IO.UTF8 import System.IO.UTF8
#endif #endif
import Hledger.Data.Utils
import Hledger.Data.Types import Hledger.Data
import Hledger.Data.Dates import Hledger.Read.Utils
import Hledger.Data.AccountName (accountNameFromComponents,accountNameComponents)
import Hledger.Data.Amount
import Hledger.Data.Transaction
import Hledger.Data.Posting
import Hledger.Data.Journal
import Hledger.Data.Commodity (dollars,dollar,unknown,nonsimplecommoditychars)
import Hledger.Read.Common
-- let's get to it -- let's get to it
@ -154,8 +147,8 @@ parse :: FilePath -> String -> ErrorT String IO Journal
parse = parseJournalWith journalFile parse = parseJournalWith journalFile
-- | Top-level journal parser. Returns a single composite, I/O performing, -- | Top-level journal parser. Returns a single composite, I/O performing,
-- error-raising "JournalUpdate" which can be applied to an empty journal -- error-raising "JournalUpdate" (and final "JournalContext") which can be
-- to get the final result. -- applied to an empty journal to get the final result.
journalFile :: GenParser Char JournalContext (JournalUpdate,JournalContext) journalFile :: GenParser Char JournalContext (JournalUpdate,JournalContext)
journalFile = do journalFile = do
journalupdates <- many journalItem journalupdates <- many journalItem

View File

@ -50,9 +50,9 @@ where
import Control.Monad.Error (ErrorT(..)) import Control.Monad.Error (ErrorT(..))
import Text.ParserCombinators.Parsec hiding (parse) import Text.ParserCombinators.Parsec hiding (parse)
import Hledger.Data import Hledger.Data
import Hledger.Read.Common import Hledger.Read.Utils
import Hledger.Read.JournalReader (ledgerExclamationDirective, ledgerHistoricalPrice, import Hledger.Read.JournalReader (ledgerExclamationDirective, ledgerHistoricalPrice,
ledgerDefaultYear, emptyLine, ledgerdatetime) ledgerDefaultYear, emptyLine, ledgerdatetime)
reader :: Reader reader :: Reader

View File

@ -1,32 +1,20 @@
{-| {-|
Utilities common to hledger journal readers.
Common utilities for hledger data readers, such as the context (state)
that is kept while parsing a journal.
-} -}
module Hledger.Read.Common module Hledger.Read.Utils
where where
import Control.Monad.Error import Control.Monad.Error
import Hledger.Data.Utils
import Hledger.Data.Types (Journal, JournalContext(..), Commodity)
import Hledger.Data.Journal
import System.Directory (getHomeDirectory) import System.Directory (getHomeDirectory)
import System.FilePath(takeDirectory,combine) import System.FilePath(takeDirectory,combine)
import System.Time (getClockTime) import System.Time (getClockTime)
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import Hledger.Data.Types (Journal, JournalContext(..), Commodity, JournalUpdate)
import Hledger.Data.Utils
import Hledger.Data.Journal (nullctx, nulljournal, journalFinalise)
-- | A hledger data reader is a triple of format name, format-detecting predicate, and a parser to Journal.
data Reader = Reader {rFormat :: String
,rDetector :: FilePath -> String -> Bool
,rParser :: FilePath -> String -> ErrorT String IO Journal
}
-- | A JournalUpdate is some transformation of a "Journal". It can do I/O
-- or raise an error.
type JournalUpdate = ErrorT String IO (Journal -> Journal)
juSequence :: [JournalUpdate] -> JournalUpdate juSequence :: [JournalUpdate] -> JournalUpdate
juSequence us = liftM (foldr (.) id) $ sequence us juSequence us = liftM (foldr (.) id) $ sequence us