hledger/hledger-lib/Hledger/Read/CsvUtils.hs
Peter Sagerson efcea0600a feat: cli: Add tsv output (#869)
All commands that suport csv output now also support tsv output. The
data is identical, but the fields are separated by tab characters and
there is no quoting or escaping. Tab, carriage return, and newline
characters in data are converted to spaces (this should rarely if ever
happen in practice).
2023-11-06 16:46:04 -08:00

57 lines
1.3 KiB
Haskell

--- * -*- outline-regexp:"--- \\*"; -*-
--- ** doc
{-|
CSV utilities.
-}
--- ** language
{-# LANGUAGE OverloadedStrings #-}
--- ** exports
module Hledger.Read.CsvUtils (
CSV, CsvRecord, CsvValue,
printCSV,
printTSV,
-- * Tests
tests_CsvUtils,
)
where
--- ** imports
import Prelude hiding (Applicative(..))
import Data.List (intersperse)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Hledger.Utils
--- ** doctest setup
-- $setup
-- >>> :set -XOverloadedStrings
type CSV = [CsvRecord]
type CsvRecord = [CsvValue]
type CsvValue = Text
printCSV :: [CsvRecord] -> TL.Text
printCSV = TB.toLazyText . unlinesB . map printRecord
where printRecord = foldMap TB.fromText . intersperse "," . map printField
printField = wrap "\"" "\"" . T.replace "\"" "\"\""
printTSV :: [CsvRecord] -> TL.Text
printTSV = TB.toLazyText . unlinesB . map printRecord
where printRecord = foldMap TB.fromText . intersperse "\t" . map printField
printField = T.map replaceWhitespace
replaceWhitespace c | c `elem` ['\t', '\n', '\r'] = ' '
replaceWhitespace c = c
--- ** tests
tests_CsvUtils :: TestTree
tests_CsvUtils = testGroup "CsvUtils" [
]