{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE CPP, DataKinds, DeriveLift, FlexibleContexts, FlexibleInstances, GADTs,
             LambdaCase, OverloadedStrings, RankNTypes,
             ScopedTypeVariables, TemplateHaskell, TypeApplications,
             TypeOperators #-}
-- | Infer row types from comma-separated values (CSV) data and read
-- that data from files. Template Haskell is used to generate the
-- necessary types so that you can write type safe programs referring
-- to those types.
module Frames.CSV where
import Control.Exception (try, IOException)
import Control.Monad (when, unless)
import qualified Data.ByteString.Char8 as B8
import qualified Data.Foldable as F
import Data.List (intercalate)
import Data.Maybe (isNothing, fromMaybe)
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import Data.Proxy
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import Data.Vinyl (recordToList, Rec(..), ElField(..), RecordToList)
import Data.Vinyl (RecMapMethod, rmapMethod, RMap, rmap)
import Data.Vinyl.Class.Method (PayloadType)
import Data.Vinyl.Functor (Const(..), (:.), Compose(..))
import Frames.Col
import Frames.ColumnTypeable
import Frames.Rec
import Frames.RecF
import Frames.ShowCSV
import GHC.TypeLits (KnownSymbol)
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Pipes ((>->))
import qualified Pipes as P
import qualified Pipes.Prelude as P
import qualified Pipes.Parse as P
import qualified Pipes.Safe as P
import qualified Pipes.Safe.Prelude as Safe
import System.IO (Handle, IOMode(ReadMode, WriteMode))

-- * Parsing

type Separator = T.Text

type QuoteChar = Char

data QuotingMode
    -- | No quoting enabled. The separator may not appear in values
  = NoQuoting
    -- | Quoted values with the given quoting character. Quotes are escaped by doubling them.
    -- Mostly RFC4180 compliant, except doesn't support newlines in values
  | RFC4180Quoting QuoteChar
  deriving (QuotingMode -> QuotingMode -> Bool
(QuotingMode -> QuotingMode -> Bool)
-> (QuotingMode -> QuotingMode -> Bool) -> Eq QuotingMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QuotingMode -> QuotingMode -> Bool
$c/= :: QuotingMode -> QuotingMode -> Bool
== :: QuotingMode -> QuotingMode -> Bool
$c== :: QuotingMode -> QuotingMode -> Bool
Eq, Int -> QuotingMode -> ShowS
[QuotingMode] -> ShowS
QuotingMode -> String
(Int -> QuotingMode -> ShowS)
-> (QuotingMode -> String)
-> ([QuotingMode] -> ShowS)
-> Show QuotingMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QuotingMode] -> ShowS
$cshowList :: [QuotingMode] -> ShowS
show :: QuotingMode -> String
$cshow :: QuotingMode -> String
showsPrec :: Int -> QuotingMode -> ShowS
$cshowsPrec :: Int -> QuotingMode -> ShowS
Show, QuotingMode -> Q Exp
QuotingMode -> Q (TExp QuotingMode)
(QuotingMode -> Q Exp)
-> (QuotingMode -> Q (TExp QuotingMode)) -> Lift QuotingMode
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: QuotingMode -> Q (TExp QuotingMode)
$cliftTyped :: QuotingMode -> Q (TExp QuotingMode)
lift :: QuotingMode -> Q Exp
$clift :: QuotingMode -> Q Exp
Lift)

data ParserOptions = ParserOptions { ParserOptions -> Maybe [Text]
headerOverride :: Maybe [T.Text]
                                   , ParserOptions -> Text
columnSeparator :: Separator
                                   , ParserOptions -> QuotingMode
quotingMode :: QuotingMode }
  deriving (ParserOptions -> ParserOptions -> Bool
(ParserOptions -> ParserOptions -> Bool)
-> (ParserOptions -> ParserOptions -> Bool) -> Eq ParserOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParserOptions -> ParserOptions -> Bool
$c/= :: ParserOptions -> ParserOptions -> Bool
== :: ParserOptions -> ParserOptions -> Bool
$c== :: ParserOptions -> ParserOptions -> Bool
Eq, Int -> ParserOptions -> ShowS
[ParserOptions] -> ShowS
ParserOptions -> String
(Int -> ParserOptions -> ShowS)
-> (ParserOptions -> String)
-> ([ParserOptions] -> ShowS)
-> Show ParserOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParserOptions] -> ShowS
$cshowList :: [ParserOptions] -> ShowS
show :: ParserOptions -> String
$cshow :: ParserOptions -> String
showsPrec :: Int -> ParserOptions -> ShowS
$cshowsPrec :: Int -> ParserOptions -> ShowS
Show)

instance Lift ParserOptions where
  lift :: ParserOptions -> Q Exp
lift (ParserOptions Maybe [Text]
Nothing Text
sep QuotingMode
quoting) = [|ParserOptions Nothing $sep' $quoting'|]
    where sep' :: Q Exp
sep' = [|T.pack $(stringE $ T.unpack sep)|]
          quoting' :: Q Exp
quoting' = QuotingMode -> Q Exp
forall t. Lift t => t -> Q Exp
lift QuotingMode
quoting
  lift (ParserOptions (Just [Text]
hs) Text
sep QuotingMode
quoting) = [|ParserOptions (Just $hs') $sep' $quoting'|]
    where sep' :: Q Exp
sep' = [|T.pack $(stringE $ T.unpack sep)|]
          hs' :: Q Exp
hs' = [|map T.pack $(listE $  map (stringE . T.unpack) hs)|]
          quoting' :: Q Exp
quoting' = QuotingMode -> Q Exp
forall t. Lift t => t -> Q Exp
lift QuotingMode
quoting
#if MIN_VERSION_template_haskell(2,16,0)
#if MIN_VERSION_template_haskell(2,17,0)
  liftTyped = liftCode . unsafeTExpCoerce . lift
#else
  liftTyped :: ParserOptions -> Q (TExp ParserOptions)
liftTyped = Q Exp -> Q (TExp ParserOptions)
forall a. Q Exp -> Q (TExp a)
unsafeTExpCoerce (Q Exp -> Q (TExp ParserOptions))
-> (ParserOptions -> Q Exp)
-> ParserOptions
-> Q (TExp ParserOptions)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserOptions -> Q Exp
forall t. Lift t => t -> Q Exp
lift
#endif
#endif

-- | Default 'ParseOptions' get column names from a header line, and
-- use commas to separate columns.
defaultParser :: ParserOptions
defaultParser :: ParserOptions
defaultParser = Maybe [Text] -> Text -> QuotingMode -> ParserOptions
ParserOptions Maybe [Text]
forall a. Maybe a
Nothing Text
defaultSep (QuoteChar -> QuotingMode
RFC4180Quoting QuoteChar
'\"')

-- | Default separator string.
defaultSep :: Separator
defaultSep :: Text
defaultSep = String -> Text
T.pack String
","

-- | Helper to split a 'T.Text' on commas and strip leading and
-- trailing whitespace from each resulting chunk.
tokenizeRow :: ParserOptions -> T.Text -> [T.Text]
tokenizeRow :: ParserOptions -> Text -> [Text]
tokenizeRow ParserOptions
options =
    [Text] -> [Text]
handleQuoting ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
sep
  where sep :: Text
sep = ParserOptions -> Text
columnSeparator ParserOptions
options
        quoting :: QuotingMode
quoting = ParserOptions -> QuotingMode
quotingMode ParserOptions
options
        handleQuoting :: [Text] -> [Text]
handleQuoting = case QuotingMode
quoting of
          QuotingMode
NoQuoting -> [Text] -> [Text]
forall a. a -> a
id
          RFC4180Quoting QuoteChar
quote -> Text -> QuoteChar -> [Text] -> [Text]
reassembleRFC4180QuotedParts Text
sep QuoteChar
quote

-- | Post processing applied to a list of tokens split by the
-- separator which should have quoted sections reassembeld
reassembleRFC4180QuotedParts :: Separator -> QuoteChar -> [T.Text] -> [T.Text]
reassembleRFC4180QuotedParts :: Text -> QuoteChar -> [Text] -> [Text]
reassembleRFC4180QuotedParts Text
sep QuoteChar
quoteChar = [Text] -> [Text]
go
  where go :: [Text] -> [Text]
go [] = []
        go (Text
part:[Text]
parts)
          | Text -> Bool
T.null Text
part = Text
T.empty Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
go [Text]
parts
          | Text -> Bool
prefixQuoted Text
part =
            if Text -> Bool
suffixQuoted Text
part
            then Text -> Text
unescape (Int -> Text -> Text
T.drop Int
1 (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Text
T.dropEnd Int
1 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
part) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
go [Text]
parts
            else case (Text -> Bool) -> [Text] -> ([Text], [Text])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Text -> Bool
suffixQuoted [Text]
parts of
                   ([Text]
h,[]) -> [Text -> Text
unescape (Text -> [Text] -> Text
T.intercalate Text
sep (Int -> Text -> Text
T.drop Int
1 Text
part Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
h))]
                   ([Text]
h,Text
t:[Text]
ts) -> Text -> Text
unescape
                                 (Text -> [Text] -> Text
T.intercalate
                                    Text
sep
                                    (Int -> Text -> Text
T.drop Int
1 Text
part Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
h [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Int -> Text -> Text
T.dropEnd Int
1 Text
t]))
                               Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
go [Text]
ts
          | Bool
otherwise = Text -> Text
T.strip Text
part Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
go [Text]
parts

        prefixQuoted :: Text -> Bool
prefixQuoted Text
t =
          Text -> QuoteChar
T.head Text
t QuoteChar -> QuoteChar -> Bool
forall a. Eq a => a -> a -> Bool
== QuoteChar
quoteChar--  &&
          -- T.length (T.takeWhile (== quoteChar) t) `rem` 2 == 1

        suffixQuoted :: Text -> Bool
suffixQuoted Text
t =
          Text
quoteText Text -> Text -> Bool
`T.isSuffixOf` Text
t--  &&
          -- T.length (T.takeWhileEnd (== quoteChar) t) `rem` 2 == 1

        quoteText :: Text
quoteText = QuoteChar -> Text
T.singleton QuoteChar
quoteChar

        unescape :: T.Text -> T.Text
        unescape :: Text -> Text
unescape = Text -> Text -> Text -> Text
T.replace Text
q2 Text
quoteText
          where q2 :: Text
q2 = Text
quoteText Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
quoteText

--tokenizeRow :: Separator -> T.Text -> [T.Text]
--tokenizeRow sep = map (unquote . T.strip) . T.splitOn sep
--  where unquote txt
--          | quoted txt = case T.dropEnd 1 (T.drop 1 txt) of
--                           txt' | T.null txt' -> "Col"
--                                | numish txt' -> txt
--                                | otherwise -> txt'
--          | otherwise = txt
--        numish = T.all (`elem` ("-+.0123456789"::String))
--        quoted txt = case T.uncons txt of
--                       Just ('"', rst)
--                         | not (T.null rst) -> T.last rst == '"'
--                       _ -> False

-- | Infer column types from a prefix (up to 1000 lines) of a CSV
-- file.
prefixInference :: (ColumnTypeable a, Monoid a, Monad m)
                => P.Parser [T.Text] m [a]
prefixInference :: Parser [Text] m [a]
prefixInference = StateT (Producer [Text] m x) m (Maybe [Text])
forall (m :: * -> *) a. Monad m => Parser a m (Maybe a)
P.draw StateT (Producer [Text] m x) m (Maybe [Text])
-> (Maybe [Text] -> StateT (Producer [Text] m x) m [a])
-> StateT (Producer [Text] m x) m [a]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  Maybe [Text]
Nothing -> [a] -> StateT (Producer [Text] m x) m [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  Just [Text]
row1 -> ([a] -> [Text] -> [a])
-> [a] -> ([a] -> [a]) -> Parser [Text] m [a]
forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Parser a m b
P.foldAll (\[a]
ts -> (a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) [a]
ts ([a] -> [a]) -> ([Text] -> [a]) -> [Text] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [a]
inferCols)
                         ([Text] -> [a]
inferCols [Text]
row1)
                         [a] -> [a]
forall a. a -> a
id
  where inferCols :: [Text] -> [a]
inferCols = (Text -> a) -> [Text] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Text -> a
forall a. ColumnTypeable a => Text -> a
inferType

-- | Extract column names and inferred types from a CSV file.
readColHeaders :: (ColumnTypeable a, Monoid a, Monad m)
               => ParserOptions -> P.Producer [T.Text] m () -> m [(T.Text, a)]
readColHeaders :: ParserOptions -> Producer [Text] m () -> m [(Text, a)]
readColHeaders ParserOptions
opts = StateT (Producer [Text] m ()) m [(Text, a)]
-> Producer [Text] m () -> m [(Text, a)]
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
P.evalStateT (StateT (Producer [Text] m ()) m [(Text, a)]
 -> Producer [Text] m () -> m [(Text, a)])
-> StateT (Producer [Text] m ()) m [(Text, a)]
-> Producer [Text] m ()
-> m [(Text, a)]
forall a b. (a -> b) -> a -> b
$
  do [Text]
headerRow <- StateT (Producer [Text] m ()) m [Text]
-> ([Text] -> StateT (Producer [Text] m ()) m [Text])
-> Maybe [Text]
-> StateT (Producer [Text] m ()) m [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [Text]
forall a. a
err (Maybe [Text] -> [Text])
-> StateT (Producer [Text] m ()) m (Maybe [Text])
-> StateT (Producer [Text] m ()) m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT (Producer [Text] m ()) m (Maybe [Text])
forall (m :: * -> *) a. Monad m => Parser a m (Maybe a)
P.draw)
                        [Text] -> StateT (Producer [Text] m ()) m [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
                        (ParserOptions -> Maybe [Text]
headerOverride ParserOptions
opts)
     [a]
colTypes <- StateT (Producer [Text] m ()) m [a]
forall a (m :: * -> *).
(ColumnTypeable a, Monoid a, Monad m) =>
Parser [Text] m [a]
prefixInference
     Bool
-> StateT (Producer [Text] m ()) m ()
-> StateT (Producer [Text] m ()) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
headerRow Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
colTypes) (String -> StateT (Producer [Text] m ()) m ()
forall a. HasCallStack => String -> a
error String
errNumColumns)
     [(Text, a)] -> StateT (Producer [Text] m ()) m [(Text, a)]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> [a] -> [(Text, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
headerRow [a]
colTypes)
  where err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"Empty Producer has no header row"
        errNumColumns :: String
errNumColumns =
          [String] -> String
unlines
          [ String
""
          , String
"Error parsing CSV: "
          , String
"  Number of columns in header differs from number of columns"
          , String
"  found in the remaining file. This may be due to newlines"
          , String
"  being present within the data itself (not just separating"
          , String
"  rows). If support for embedded newlines is required, "
          , String
"  consider using the Frames-dsv package in conjunction with"
          , String
"  Frames to make use of a different CSV parser."]

-- * Loading CSV Data

-- | Parsing each component of a 'RecF' from a list of text chunks,
-- one chunk per record component.
class ReadRec rs where
  readRec :: [T.Text] -> Rec (Either T.Text :. ElField) rs

instance ReadRec '[] where
  readRec :: [Text] -> Rec (Either Text :. ElField) '[]
readRec [Text]
_ = Rec (Either Text :. ElField) '[]
forall u (a :: u -> *). Rec a '[]
RNil

instance (Parseable t, ReadRec ts, KnownSymbol s) => ReadRec (s :-> t ': ts) where
  readRec :: [Text] -> Rec (Either Text :. ElField) ((s :-> t) : ts)
readRec [] = Either Text (ElField (s :-> t))
-> Compose (Either Text) ElField (s :-> t)
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose (Text -> Either Text (ElField (s :-> t))
forall a b. a -> Either a b
Left Text
forall a. Monoid a => a
mempty) Compose (Either Text) ElField (s :-> t)
-> Rec (Either Text :. ElField) ts
-> Rec (Either Text :. ElField) ((s :-> t) : ts)
forall u (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& [Text] -> Rec (Either Text :. ElField) ts
forall (rs :: [(Symbol, *)]).
ReadRec rs =>
[Text] -> Rec (Either Text :. ElField) rs
readRec []
  readRec (Text
h:[Text]
t) = Compose (Either Text) ElField (s :-> t)
-> (t -> Compose (Either Text) ElField (s :-> t))
-> Maybe t
-> Compose (Either Text) ElField (s :-> t)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Either Text (ElField (s :-> t))
-> Compose (Either Text) ElField (s :-> t)
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose (Text -> Either Text (ElField (s :-> t))
forall a b. a -> Either a b
Left (Text -> Text
T.copy Text
h)))
                        (Either Text (ElField (s :-> t))
-> Compose (Either Text) ElField (s :-> t)
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose (Either Text (ElField (s :-> t))
 -> Compose (Either Text) ElField (s :-> t))
-> (t -> Either Text (ElField (s :-> t)))
-> t
-> Compose (Either Text) ElField (s :-> t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElField (s :-> t) -> Either Text (ElField (s :-> t))
forall a b. b -> Either a b
Right (ElField (s :-> t) -> Either Text (ElField (s :-> t)))
-> (t -> ElField (s :-> t)) -> t -> Either Text (ElField (s :-> t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> ElField (s :-> t)
forall (s :: Symbol) t. KnownSymbol s => t -> ElField '(s, t)
Field)
                        (Text -> Maybe t
forall (m :: * -> *) a. (MonadPlus m, Parseable a) => Text -> m a
parse' Text
h) Compose (Either Text) ElField (s :-> t)
-> Rec (Either Text :. ElField) ts
-> Rec (Either Text :. ElField) ((s :-> t) : ts)
forall u (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& [Text] -> Rec (Either Text :. ElField) ts
forall (rs :: [(Symbol, *)]).
ReadRec rs =>
[Text] -> Rec (Either Text :. ElField) rs
readRec [Text]
t

-- | Opens a file (in 'P.MonadSafe') and repeatedly applies the given
-- function to the 'Handle' to obtain lines to yield. Adapted from the
-- moribund pipes-text package.
pipeLines :: P.MonadSafe m
          => (Handle -> IO (Either IOException T.Text))
          -> FilePath
          -> P.Producer T.Text m ()
pipeLines :: (Handle -> IO (Either IOException Text))
-> String -> Producer Text m ()
pipeLines Handle -> IO (Either IOException Text)
pgetLine String
fp = String
-> IOMode -> (Handle -> Producer Text m ()) -> Producer Text m ()
forall (m :: * -> *) r.
MonadSafe m =>
String -> IOMode -> (Handle -> m r) -> m r
Safe.withFile String
fp IOMode
ReadMode ((Handle -> Producer Text m ()) -> Producer Text m ())
-> (Handle -> Producer Text m ()) -> Producer Text m ()
forall a b. (a -> b) -> a -> b
$ \Handle
h ->
  let loop :: Producer Text m ()
loop = do Either IOException Text
txt <- IO (Either IOException Text)
-> Proxy X () () Text m (Either IOException Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
P.liftIO (Handle -> IO (Either IOException Text)
pgetLine Handle
h)
                case Either IOException Text
txt of
                  Left IOException
_e -> () -> Producer Text m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                  Right Text
y -> Text -> Producer Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
P.yield Text
y Producer Text m () -> Producer Text m () -> Producer Text m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m ()
loop
  in Producer Text m ()
loop

-- | Produce lines of 'T.Text'.
produceTextLines :: P.MonadSafe m => FilePath -> P.Producer T.Text m ()
produceTextLines :: String -> Producer Text m ()
produceTextLines = (Handle -> IO (Either IOException Text))
-> String -> Producer Text m ()
forall (m :: * -> *).
MonadSafe m =>
(Handle -> IO (Either IOException Text))
-> String -> Producer Text m ()
pipeLines (IO Text -> IO (Either IOException Text)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO Text -> IO (Either IOException Text))
-> (Handle -> IO Text) -> Handle -> IO (Either IOException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO Text
T.hGetLine)

-- | Produce lines of tokens that were separated by the given
-- separator.
produceTokens :: P.MonadSafe m
              => FilePath
              -> Separator
              -> P.Producer [T.Text] m ()
produceTokens :: String -> Text -> Producer [Text] m ()
produceTokens String
fp Text
sep = String -> Producer Text m ()
forall (m :: * -> *). MonadSafe m => String -> Producer Text m ()
produceTextLines String
fp Producer Text m ()
-> Proxy () Text () [Text] m () -> Producer [Text] m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> (Text -> [Text]) -> Proxy () Text () [Text] m ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map Text -> [Text]
tokenize
  where tokenize :: Text -> [Text]
tokenize = ParserOptions -> Text -> [Text]
tokenizeRow ParserOptions
popts
        popts :: ParserOptions
popts = ParserOptions
defaultParser { columnSeparator :: Text
columnSeparator = Text
sep }

-- | Consume lines of 'T.Text', writing them to a file.
consumeTextLines :: P.MonadSafe m => FilePath -> P.Consumer T.Text m r
consumeTextLines :: String -> Consumer Text m r
consumeTextLines String
fp = String
-> IOMode -> (Handle -> Consumer Text m r) -> Consumer Text m r
forall (m :: * -> *) r.
MonadSafe m =>
String -> IOMode -> (Handle -> m r) -> m r
Safe.withFile String
fp IOMode
WriteMode ((Handle -> Consumer Text m r) -> Consumer Text m r)
-> (Handle -> Consumer Text m r) -> Consumer Text m r
forall a b. (a -> b) -> a -> b
$ \Handle
h ->
  let loop :: Consumer Text m r
loop = Proxy () Text () X m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
P.await Proxy () Text () X m Text
-> (Text -> Proxy () Text () X m ()) -> Proxy () Text () X m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> Proxy () Text () X m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
P.liftIO (IO () -> Proxy () Text () X m ())
-> (Text -> IO ()) -> Text -> Proxy () Text () X m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Text -> IO ()
T.hPutStrLn Handle
h Proxy () Text () X m () -> Consumer Text m r -> Consumer Text m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Consumer Text m r
loop
  in Consumer Text m r
loop

-- | Produce the lines of a latin1 (or ISO8859 Part 1) encoded file as
-- ’T.Text’ values.
readFileLatin1Ln :: P.MonadSafe m => FilePath -> P.Producer [T.Text] m ()
readFileLatin1Ln :: String -> Producer [Text] m ()
readFileLatin1Ln String
fp = (Handle -> IO (Either IOException Text))
-> String -> Producer Text m ()
forall (m :: * -> *).
MonadSafe m =>
(Handle -> IO (Either IOException Text))
-> String -> Producer Text m ()
pipeLines (IO Text -> IO (Either IOException Text)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO Text -> IO (Either IOException Text))
-> (Handle -> IO Text) -> Handle -> IO (Either IOException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Text) -> IO ByteString -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
T.decodeLatin1 (IO ByteString -> IO Text)
-> (Handle -> IO ByteString) -> Handle -> IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO ByteString
B8.hGetLine) String
fp
                      Producer Text m ()
-> Proxy () Text () [Text] m () -> Producer [Text] m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> (Text -> [Text]) -> Proxy () Text () [Text] m ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map (ParserOptions -> Text -> [Text]
tokenizeRow ParserOptions
defaultParser)

-- | Read a 'RecF' from one line of CSV.
readRow :: ReadRec rs
        => ParserOptions -> T.Text -> Rec (Either T.Text :. ElField) rs
readRow :: ParserOptions -> Text -> Rec (Either Text :. ElField) rs
readRow = ([Text] -> Rec (Either Text :. ElField) rs
forall (rs :: [(Symbol, *)]).
ReadRec rs =>
[Text] -> Rec (Either Text :. ElField) rs
readRec ([Text] -> Rec (Either Text :. ElField) rs)
-> (Text -> [Text]) -> Text -> Rec (Either Text :. ElField) rs
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Text -> [Text]) -> Text -> Rec (Either Text :. ElField) rs)
-> (ParserOptions -> Text -> [Text])
-> ParserOptions
-> Text
-> Rec (Either Text :. ElField) rs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserOptions -> Text -> [Text]
tokenizeRow

-- | Produce rows where any given entry can fail to parse.
readTableMaybeOpt :: (P.MonadSafe m, ReadRec rs, RMap rs)
                  => ParserOptions
                  -> FilePath
                  -> P.Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybeOpt :: ParserOptions
-> String -> Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybeOpt ParserOptions
opts String
csvFile =
  String -> Text -> Producer [Text] m ()
forall (m :: * -> *).
MonadSafe m =>
String -> Text -> Producer [Text] m ()
produceTokens String
csvFile (ParserOptions -> Text
columnSeparator ParserOptions
opts) Producer [Text] m ()
-> Proxy () [Text] () (Rec (Maybe :. ElField) rs) m ()
-> Producer (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> ParserOptions
-> Proxy () [Text] () (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(Monad m, ReadRec rs, RMap rs) =>
ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybeOpt ParserOptions
opts
{-# INLINE readTableMaybeOpt #-}

-- | Stream lines of CSV data into rows of ’Rec’ values values where
-- any given entry can fail to parse.
pipeTableMaybeOpt :: (Monad m, ReadRec rs, RMap rs)
                  => ParserOptions
                  -> P.Pipe [T.Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybeOpt :: ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybeOpt ParserOptions
opts = do
  Bool
-> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
-> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe [Text] -> Bool
forall a. Maybe a -> Bool
isNothing (ParserOptions -> Maybe [Text]
headerOverride ParserOptions
opts)) (() ()
-> Proxy () [Text] () (Rec (Maybe :. ElField) rs) m [Text]
-> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Proxy () [Text] () (Rec (Maybe :. ElField) rs) m [Text]
forall (m :: * -> *) a. Functor m => Consumer' a m a
P.await)
  ([Text] -> Rec (Maybe :. ElField) rs)
-> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((forall (x :: (Symbol, *)).
 (:.) (Either Text) ElField x -> (:.) Maybe ElField x)
-> Rec (Either Text :. ElField) rs -> Rec (Maybe :. ElField) rs
forall u (rs :: [u]) (f :: u -> *) (g :: u -> *).
RMap rs =>
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
rmap ((Text -> Compose Maybe ElField x)
-> (ElField x -> Compose Maybe ElField x)
-> Either Text (ElField x)
-> Compose Maybe ElField x
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Compose Maybe ElField x -> Text -> Compose Maybe ElField x
forall a b. a -> b -> a
const (Maybe (ElField x) -> Compose Maybe ElField x
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose Maybe (ElField x)
forall a. Maybe a
Nothing))
                      (Maybe (ElField x) -> Compose Maybe ElField x
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose (Maybe (ElField x) -> Compose Maybe ElField x)
-> (ElField x -> Maybe (ElField x))
-> ElField x
-> Compose Maybe ElField x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElField x -> Maybe (ElField x)
forall a. a -> Maybe a
Just) (Either Text (ElField x) -> Compose Maybe ElField x)
-> (Compose (Either Text) ElField x -> Either Text (ElField x))
-> Compose (Either Text) ElField x
-> Compose Maybe ElField x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose (Either Text) ElField x -> Either Text (ElField x)
forall l (f :: l -> *) k (g :: k -> l) (x :: k).
Compose f g x -> f (g x)
getCompose)
         (Rec (Either Text :. ElField) rs -> Rec (Maybe :. ElField) rs)
-> ([Text] -> Rec (Either Text :. ElField) rs)
-> [Text]
-> Rec (Maybe :. ElField) rs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Rec (Either Text :. ElField) rs
forall (rs :: [(Symbol, *)]).
ReadRec rs =>
[Text] -> Rec (Either Text :. ElField) rs
readRec)
{-# INLINE pipeTableMaybeOpt #-}

-- | Stream lines of CSV data into rows of ’Rec’ values values where
-- any given entry can fail to parse. In the case of a parse failure, the
-- raw 'T.Text' of that entry is retained.
pipeTableEitherOpt :: (Monad m, ReadRec rs)
                   => ParserOptions
                   -> P.Pipe T.Text (Rec (Either T.Text :. ElField) rs) m ()
pipeTableEitherOpt :: ParserOptions -> Pipe Text (Rec (Either Text :. ElField) rs) m ()
pipeTableEitherOpt ParserOptions
opts = do
  Bool
-> Pipe Text (Rec (Either Text :. ElField) rs) m ()
-> Pipe Text (Rec (Either Text :. ElField) rs) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe [Text] -> Bool
forall a. Maybe a -> Bool
isNothing (ParserOptions -> Maybe [Text]
headerOverride ParserOptions
opts)) (() ()
-> Proxy () Text () (Rec (Either Text :. ElField) rs) m Text
-> Pipe Text (Rec (Either Text :. ElField) rs) m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Proxy () Text () (Rec (Either Text :. ElField) rs) m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
P.await)
  (Text -> Rec (Either Text :. ElField) rs)
-> Pipe Text (Rec (Either Text :. ElField) rs) m ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map (ParserOptions -> Text -> Rec (Either Text :. ElField) rs
forall (rs :: [(Symbol, *)]).
ReadRec rs =>
ParserOptions -> Text -> Rec (Either Text :. ElField) rs
readRow ParserOptions
opts)
{-# INLINE pipeTableEitherOpt #-}

-- | Produce rows where any given entry can fail to parse.
readTableMaybe :: (P.MonadSafe m, ReadRec rs, RMap rs)
               => FilePath -> P.Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybe :: String -> Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybe = ParserOptions
-> String -> Producer (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(MonadSafe m, ReadRec rs, RMap rs) =>
ParserOptions
-> String -> Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybeOpt ParserOptions
defaultParser
{-# INLINE readTableMaybe #-}

-- | Stream lines of CSV data into rows of ’Rec’ values where any
-- given entry can fail to parse.
pipeTableMaybe :: (Monad m, ReadRec rs, RMap rs)
               => P.Pipe [T.Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybe :: Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybe = ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(Monad m, ReadRec rs, RMap rs) =>
ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybeOpt ParserOptions
defaultParser
{-# INLINE pipeTableMaybe #-}

-- | Stream lines of CSV data into rows of ’Rec’ values where any
-- given entry can fail to parse. In the case of a parse failure, the
-- raw 'T.Text' of that entry is retained.
pipeTableEither :: (Monad m, ReadRec rs)
                => P.Pipe T.Text (Rec (Either T.Text :. ElField) rs) m ()
pipeTableEither :: Pipe Text (Rec (Either Text :. ElField) rs) m ()
pipeTableEither = ParserOptions -> Pipe Text (Rec (Either Text :. ElField) rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(Monad m, ReadRec rs) =>
ParserOptions -> Pipe Text (Rec (Either Text :. ElField) rs) m ()
pipeTableEitherOpt ParserOptions
defaultParser
{-# INLINE pipeTableEither #-}

-- -- | Returns a `MonadPlus` producer of rows for which each column was
-- -- successfully parsed. This is typically slower than 'readTableOpt'.
-- readTableOpt' :: forall m rs.
--                  (MonadPlus m, MonadIO m, ReadRec rs)
--               => ParserOptions -> FilePath -> m (Record rs)
-- readTableOpt' opts csvFile =
--   do h <- liftIO $ do
--             h <- openFile csvFile ReadMode
--             when (isNothing $ headerOverride opts) (void $ T.hGetLine h)
--             return h
--      let go = liftIO (hIsEOF h) >>= \case
--               True -> mzero
--               False -> let r = recMaybe . readRow opts <$> T.hGetLine h
--                        in liftIO r >>= maybe go (flip mplus go . return)
--      go
-- {-# INLINE readTableOpt' #-}

-- -- | Returns a `MonadPlus` producer of rows for which each column was
-- -- successfully parsed. This is typically slower than 'readTable'.
-- readTable' :: forall m rs. (P.MonadSafe m, ReadRec rs)
--            => FilePath -> m (Record rs)
-- readTable' = readTableOpt' defaultParser
-- {-# INLINE readTable' #-}

-- | Returns a producer of rows for which each column was successfully
-- parsed.
readTableOpt :: (P.MonadSafe m, ReadRec rs, RMap rs)
             => ParserOptions -> FilePath -> P.Producer (Record rs) m ()
readTableOpt :: ParserOptions -> String -> Producer (Record rs) m ()
readTableOpt ParserOptions
opts String
csvFile = ParserOptions
-> String -> Producer (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(MonadSafe m, ReadRec rs, RMap rs) =>
ParserOptions
-> String -> Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybeOpt ParserOptions
opts String
csvFile Producer (Rec (Maybe :. ElField) rs) m ()
-> Proxy () (Rec (Maybe :. ElField) rs) () (Record rs) m ()
-> Producer (Record rs) m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
P.>-> Proxy () (Rec (Maybe :. ElField) rs) () (Record rs) m ()
forall (cs :: [(Symbol, *)]) b.
Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
go
  where go :: Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
go = Proxy
  ()
  (Rec (Maybe :. ElField) cs)
  ()
  (Record cs)
  m
  (Rec (Maybe :. ElField) cs)
forall (m :: * -> *) a. Functor m => Consumer' a m a
P.await Proxy
  ()
  (Rec (Maybe :. ElField) cs)
  ()
  (Record cs)
  m
  (Rec (Maybe :. ElField) cs)
-> (Rec (Maybe :. ElField) cs
    -> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b)
-> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
-> (Record cs
    -> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b)
-> Maybe (Record cs)
-> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
go (\Record cs
x -> Record cs
-> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
P.yield Record cs
x Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m ()
-> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
-> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
go) (Maybe (Record cs)
 -> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b)
-> (Rec (Maybe :. ElField) cs -> Maybe (Record cs))
-> Rec (Maybe :. ElField) cs
-> Proxy () (Rec (Maybe :. ElField) cs) () (Record cs) m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rec (Maybe :. ElField) cs -> Maybe (Record cs)
forall (cs :: [(Symbol, *)]).
Rec (Maybe :. ElField) cs -> Maybe (Record cs)
recMaybe
{-# INLINE readTableOpt #-}

-- | Pipe lines of CSV text into rows for which each column was
-- successfully parsed.
pipeTableOpt :: (ReadRec rs, RMap rs, Monad m)
             => ParserOptions -> P.Pipe [T.Text] (Record rs) m ()
pipeTableOpt :: ParserOptions -> Pipe [Text] (Record rs) m ()
pipeTableOpt ParserOptions
opts = ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(Monad m, ReadRec rs, RMap rs) =>
ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybeOpt ParserOptions
opts Pipe [Text] (Rec (Maybe :. ElField) rs) m ()
-> Proxy () (Rec (Maybe :. ElField) rs) () (Maybe (Record rs)) m ()
-> Proxy () [Text] () (Maybe (Record rs)) m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> (Rec (Maybe :. ElField) rs -> Maybe (Record rs))
-> Proxy () (Rec (Maybe :. ElField) rs) () (Maybe (Record rs)) m ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map Rec (Maybe :. ElField) rs -> Maybe (Record rs)
forall (cs :: [(Symbol, *)]).
Rec (Maybe :. ElField) cs -> Maybe (Record cs)
recMaybe Proxy () [Text] () (Maybe (Record rs)) m ()
-> Proxy () (Maybe (Record rs)) () (Record rs) m ()
-> Pipe [Text] (Record rs) m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> Proxy () (Maybe (Record rs)) () (Record rs) m ()
forall (m :: * -> *) (f :: * -> *) a r.
(Functor m, Foldable f) =>
Pipe (f a) a m r
P.concat
{-# INLINE pipeTableOpt #-}

-- | Returns a producer of rows for which each column was successfully
-- parsed.
readTable :: (P.MonadSafe m, ReadRec rs, RMap rs)
          => FilePath -> P.Producer (Record rs) m ()
readTable :: String -> Producer (Record rs) m ()
readTable = ParserOptions -> String -> Producer (Record rs) m ()
forall (m :: * -> *) (rs :: [(Symbol, *)]).
(MonadSafe m, ReadRec rs, RMap rs) =>
ParserOptions -> String -> Producer (Record rs) m ()
readTableOpt ParserOptions
defaultParser
{-# INLINE readTable #-}

-- | Pipe lines of CSV text into rows for which each column was
-- successfully parsed.
pipeTable :: (ReadRec rs, RMap rs, Monad m)
          => P.Pipe [T.Text] (Record rs) m ()
pipeTable :: Pipe [Text] (Record rs) m ()
pipeTable = ParserOptions -> Pipe [Text] (Record rs) m ()
forall (rs :: [(Symbol, *)]) (m :: * -> *).
(ReadRec rs, RMap rs, Monad m) =>
ParserOptions -> Pipe [Text] (Record rs) m ()
pipeTableOpt ParserOptions
defaultParser
{-# INLINE pipeTable #-}

-- * Writing CSV Data

showFieldsCSV :: (RecMapMethod ShowCSV ElField ts, RecordToList ts)
              => Record ts -> [T.Text]
showFieldsCSV :: Record ts -> [Text]
showFieldsCSV = Rec (Const Text) ts -> [Text]
forall u (rs :: [u]) a. RecordToList rs => Rec (Const a) rs -> [a]
recordToList (Rec (Const Text) ts -> [Text])
-> (Record ts -> Rec (Const Text) ts) -> Record ts -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (a :: (Symbol, *)).
 ShowCSV (PayloadType ElField a) =>
 ElField a -> Const Text a)
-> Record ts -> Rec (Const Text) ts
forall u (c :: * -> Constraint) (f :: u -> *) (ts :: [u])
       (g :: u -> *).
RecMapMethod c f ts =>
(forall (a :: u). c (PayloadType f a) => f a -> g a)
-> Rec f ts -> Rec g ts
rmapMethod @ShowCSV forall (a :: (Symbol, *)).
ShowCSV (PayloadType ElField a) =>
ElField a -> Const Text a
aux
  where aux :: (ShowCSV (PayloadType ElField a))
            => ElField a -> Const T.Text a
        aux :: ElField a -> Const Text a
aux (Field t
x) = Text -> Const Text a
forall k a (b :: k). a -> Const a b
Const (t -> Text
forall a. ShowCSV a => a -> Text
showCSV t
x)

-- | 'P.yield' a header row with column names followed by a line of
-- text for each 'Record' with each field separated by a comma. If
-- your source of 'Record' values is a 'P.Producer', consider using
-- 'pipeToCSV' to keep everything streaming.
produceCSV :: forall f ts m.
              (ColumnHeaders ts, Foldable f, Monad m, RecordToList ts,
              RecMapMethod ShowCSV ElField ts)
           => f (Record ts) -> P.Producer String m ()
produceCSV :: f (Record ts) -> Producer String m ()
produceCSV f (Record ts)
recs = do
  String -> Producer String m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
P.yield (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," (Proxy (Record ts) -> [String]
forall (cs :: [(Symbol, *)]) (proxy :: * -> *)
       (f :: (Symbol, *) -> *).
ColumnHeaders cs =>
proxy (Rec f cs) -> [String]
columnHeaders (Proxy (Record ts)
forall k (t :: k). Proxy t
Proxy :: Proxy (Record ts))))
  (Record ts -> Producer String m ())
-> f (Record ts) -> Producer String m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
F.mapM_ (String -> Producer String m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
P.yield (String -> Producer String m ())
-> (Record ts -> String) -> Record ts -> Producer String m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> String) -> (Record ts -> Text) -> Record ts -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> (Record ts -> [Text]) -> Record ts -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Record ts -> [Text]
forall (ts :: [(Symbol, *)]).
(RecMapMethod ShowCSV ElField ts, RecordToList ts) =>
Record ts -> [Text]
showFieldsCSV) f (Record ts)
recs

-- | 'P.yield' a header row with column names followed by a line of
-- text for each 'Record' with each field separated by a comma. This
-- is the same as 'produceCSV', but adapated for cases where you have
-- streaming input that you wish to use to produce streaming output.
pipeToCSV :: forall ts m.
             (Monad m, ColumnHeaders ts, RecordToList ts,
              RecMapMethod ShowCSV ElField ts)
          => P.Pipe (Record ts) T.Text m ()
pipeToCSV :: Pipe (Record ts) Text m ()
pipeToCSV = Text -> Pipe (Record ts) Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
P.yield (Text -> [Text] -> Text
T.intercalate Text
"," ((String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack [String]
header)) Pipe (Record ts) Text m ()
-> Pipe (Record ts) Text m () -> Pipe (Record ts) Text m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Pipe (Record ts) Text m ()
go
  where header :: [String]
header = Proxy (Record ts) -> [String]
forall (cs :: [(Symbol, *)]) (proxy :: * -> *)
       (f :: (Symbol, *) -> *).
ColumnHeaders cs =>
proxy (Rec f cs) -> [String]
columnHeaders (Proxy (Record ts)
forall k (t :: k). Proxy t
Proxy :: Proxy (Record ts))
        go :: P.Pipe (Record ts) T.Text m ()
        go :: Pipe (Record ts) Text m ()
go = (Record ts -> Text) -> Pipe (Record ts) Text m ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map (Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> (Record ts -> [Text]) -> Record ts -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Record ts -> [Text]
forall (ts :: [(Symbol, *)]).
(RecMapMethod ShowCSV ElField ts, RecordToList ts) =>
Record ts -> [Text]
showFieldsCSV)

-- | Write a header row with column names followed by a line of text
-- for each 'Record' to the given file.
writeCSV :: (ColumnHeaders ts, Foldable f, RecordToList ts,
             RecMapMethod ShowCSV ElField ts)
         => FilePath -> f (Record ts) -> IO ()
writeCSV :: String -> f (Record ts) -> IO ()
writeCSV String
fp f (Record ts)
recs = SafeT IO () -> IO ()
forall (m :: * -> *) r.
(MonadMask m, MonadIO m) =>
SafeT m r -> m r
P.runSafeT (SafeT IO () -> IO ())
-> (Effect (SafeT IO) () -> SafeT IO ())
-> Effect (SafeT IO) ()
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Effect (SafeT IO) () -> SafeT IO ()
forall (m :: * -> *) r. Monad m => Effect m r -> m r
P.runEffect (Effect (SafeT IO) () -> IO ()) -> Effect (SafeT IO) () -> IO ()
forall a b. (a -> b) -> a -> b
$
                   f (Record ts) -> Producer String (SafeT IO) ()
forall (f :: * -> *) (ts :: [(Symbol, *)]) (m :: * -> *).
(ColumnHeaders ts, Foldable f, Monad m, RecordToList ts,
 RecMapMethod ShowCSV ElField ts) =>
f (Record ts) -> Producer String m ()
produceCSV f (Record ts)
recs Producer String (SafeT IO) ()
-> Proxy () String () Text (SafeT IO) ()
-> Proxy X () () Text (SafeT IO) ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> (String -> Text) -> Proxy () String () Text (SafeT IO) ()
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map String -> Text
T.pack Proxy X () () Text (SafeT IO) ()
-> Proxy () Text () X (SafeT IO) () -> Effect (SafeT IO) ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> String -> Proxy () Text () X (SafeT IO) ()
forall (m :: * -> *) r. MonadSafe m => String -> Consumer Text m r
consumeTextLines String
fp