--- * -*- outline-regexp:"--- \\*"; -*-
--- ** doc
-- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections.
{-|

A reader for CSV (character-separated) data.
This also reads a rules file to help interpret the CSV data.

-}

--- ** language
{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE TypeFamilies         #-}

--- ** exports
module Hledger.Read.CsvReader (
  -- * Reader
  reader,
  -- * Tests
  tests_CsvReader,
)
where

--- ** imports
import Prelude hiding (Applicative(..))
import Control.Monad.Except       (ExceptT(..), liftEither)
import Control.Monad.IO.Class     (MonadIO)
import System.IO                  (Handle)

import Hledger.Data
import Hledger.Utils
import Hledger.Read.Common (aliasesFromOpts, Reader(..), InputOpts(..), journalFinalise)
import Hledger.Read.RulesReader (readJournalFromCsv, getRulesFile, rulesEncoding, readRules)
import Control.Monad.Trans (lift)

--- ** doctest setup
-- $setup
-- >>> :set -XOverloadedStrings

--- ** reader

reader :: MonadIO m => SepFormat -> Reader m
reader :: forall (m :: * -> *). MonadIO m => SepFormat -> Reader m
reader SepFormat
sep = Reader
  {rFormat :: StorageFormat
rFormat     = SepFormat -> StorageFormat
Sep SepFormat
sep
  ,rExtensions :: [String]
rExtensions = [SepFormat -> String
forall a. Show a => a -> String
show SepFormat
sep]
  ,rReadFn :: InputOpts -> String -> Handle -> ExceptT String IO Journal
rReadFn     = SepFormat
-> InputOpts -> String -> Handle -> ExceptT String IO Journal
parse SepFormat
sep
  ,rParser :: MonadIO m => InputOpts -> ErroringJournalParser m Journal
rParser     = ErroringJournalParser m Journal
-> InputOpts -> ErroringJournalParser m Journal
forall a b. a -> b -> a
const (ErroringJournalParser m Journal
 -> InputOpts -> ErroringJournalParser m Journal)
-> ErroringJournalParser m Journal
-> InputOpts
-> ErroringJournalParser m Journal
forall a b. (a -> b) -> a -> b
$ String -> ErroringJournalParser m Journal
forall a.
String
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"sorry, CSV files can't be included yet"
    -- This unnecessarily shows the CSV file's first line in the error message,
    -- but gives a more useful message than just calling error'.
    -- XXX Note every call to error' in Hledger.Read.* is potentially a similar problem -
    -- the error message is good enough when the file was specified directly by the user,
    -- but not good if it was loaded by a possibly long chain of include directives.
  }

-- | Parse and post-process a "Journal" from a CSV(/SSV/TSV/*SV) data file, or give an error.
-- This currently ignores the provided input file handle, and reads from the data file itself,
-- inferring a corresponding rules file to help convert it.
-- This does not check balance assertions.
parse :: SepFormat -> InputOpts -> FilePath -> Handle -> ExceptT String IO Journal
parse :: SepFormat
-> InputOpts -> String -> Handle -> ExceptT String IO Journal
parse SepFormat
sep InputOpts
iopts String
f Handle
h = do
  CsvRules
rules <- String -> ExceptT String IO CsvRules
readRules (String -> ExceptT String IO CsvRules)
-> String -> ExceptT String IO CsvRules
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> String
getRulesFile String
f (InputOpts -> Maybe String
mrules_file_ InputOpts
iopts)
  Maybe DynEncoding
mencoding <- CsvRules -> ExceptT String IO (Maybe DynEncoding)
rulesEncoding CsvRules
rules
  Text
csvtext <- IO Text -> ExceptT String IO Text
forall (m :: * -> *) a. Monad m => m a -> ExceptT String m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Text -> ExceptT String IO Text)
-> IO Text -> ExceptT String IO Text
forall a b. (a -> b) -> a -> b
$ Maybe DynEncoding -> Handle -> IO Text
readHandlePortably' Maybe DynEncoding
mencoding Handle
h
  CsvRules
-> String -> Text -> Maybe SepFormat -> ExceptT String IO Journal
readJournalFromCsv CsvRules
rules String
f Text
csvtext (SepFormat -> Maybe SepFormat
forall a. a -> Maybe a
Just SepFormat
sep)
  -- apply any command line account aliases. Can fail with a bad replacement pattern.
  ExceptT String IO Journal
-> (Journal -> ExceptT String IO Journal)
-> ExceptT String IO Journal
forall a b.
ExceptT String IO a
-> (a -> ExceptT String IO b) -> ExceptT String IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either String Journal -> ExceptT String IO Journal
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Either String Journal -> ExceptT String IO Journal)
-> (Journal -> Either String Journal)
-> Journal
-> ExceptT String IO Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [AccountAlias] -> Journal -> Either String Journal
journalApplyAliases (InputOpts -> [AccountAlias]
aliasesFromOpts InputOpts
iopts)
      -- journalFinalise assumes the journal's items are
      -- reversed, as produced by JournalReader's parser.
      -- But here they are already properly ordered. So we'd
      -- better preemptively reverse them once more. XXX inefficient
      (Journal -> Either String Journal)
-> (Journal -> Journal) -> Journal -> Either String Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Journal -> Journal
journalReverse
  ExceptT String IO Journal
-> (Journal -> ExceptT String IO Journal)
-> ExceptT String IO Journal
forall a b.
ExceptT String IO a
-> (a -> ExceptT String IO b) -> ExceptT String IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= InputOpts -> String -> Text -> Journal -> ExceptT String IO Journal
journalFinalise InputOpts
iopts{balancingopts_=(balancingopts_ iopts){ignore_assertions_=True}} String
f Text
""

--- ** tests

tests_CsvReader :: TestTree
tests_CsvReader = String -> [TestTree] -> TestTree
testGroup String
"CsvReader" [
  ]