Compare commits
5 Commits
76cea1e051
...
724dfe0345
Author | SHA1 | Date | |
---|---|---|---|
Jonathan Lamothe | 724dfe0345 | ||
Jonathan Lamothe | 51784123cd | ||
Jonathan Lamothe | 35130eeae1 | ||
Jonathan Lamothe | 2af6966192 | ||
Jonathan Lamothe | 8533e84caa |
|
@ -26,6 +26,12 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||
{-# LANGUAGE LambdaCase, OverloadedStrings #-}
|
||||
|
||||
module Data.CSV.Sip (
|
||||
-- * Read an entire CSV file
|
||||
slurpCSV,
|
||||
slurpRawCSV,
|
||||
slurpLabelledCSV,
|
||||
slurpRawLabelledCSV,
|
||||
-- * Conduits
|
||||
labelFields,
|
||||
decodeRows,
|
||||
decodeRawRows,
|
||||
|
@ -33,18 +39,63 @@ module Data.CSV.Sip (
|
|||
toBytes,
|
||||
) where
|
||||
|
||||
import Conduit (ConduitT, await, mapC, yield, (.|))
|
||||
import Conduit
|
||||
( ConduitT
|
||||
, MonadResource
|
||||
, await
|
||||
, mapC
|
||||
, runConduit
|
||||
, sourceFile
|
||||
, yield
|
||||
, (.|)
|
||||
)
|
||||
import Control.Monad (unless)
|
||||
import Control.Monad.Trans.Class (lift)
|
||||
import Control.Monad.Trans.State (StateT, evalStateT, get, gets, modify)
|
||||
import qualified Data.ByteString as BS
|
||||
import Data.Conduit.List (consume)
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe (fromMaybe)
|
||||
import qualified Data.Text as T
|
||||
import Data.Text.Encoding (decodeUtf8')
|
||||
import Data.Word (Word8)
|
||||
|
||||
-- | read a CSV stream, using the first row as a header containing field labels
|
||||
-- | read an entire CSV file
|
||||
slurpCSV
|
||||
:: MonadResource m
|
||||
=> FilePath
|
||||
-- ^ the path to the file to read
|
||||
-> m [[T.Text]]
|
||||
slurpCSV file = runConduit $ sourceFile file .| decodeRows .| consume
|
||||
|
||||
-- | read an entire CSV file in raw mode
|
||||
slurpRawCSV
|
||||
:: MonadResource m
|
||||
=> FilePath
|
||||
-- ^ the path to the file to read
|
||||
-> m [[BS.ByteString]]
|
||||
slurpRawCSV file = runConduit $ sourceFile file .| decodeRawRows .| consume
|
||||
|
||||
-- | read an entire CSV file with a header
|
||||
slurpLabelledCSV
|
||||
:: MonadResource m
|
||||
=> FilePath
|
||||
-- ^ the path to the file to read
|
||||
-> m [M.Map T.Text T.Text]
|
||||
slurpLabelledCSV file = runConduit $
|
||||
sourceFile file .| decodeRows .| labelFields .|consume
|
||||
|
||||
-- | read an entire CSV file with a header
|
||||
slurpRawLabelledCSV
|
||||
:: MonadResource m
|
||||
=> FilePath
|
||||
-- ^ the path to the file to read
|
||||
-> m [M.Map BS.ByteString BS.ByteString]
|
||||
slurpRawLabelledCSV file = runConduit $
|
||||
sourceFile file .| decodeRawRows .| labelFields .|consume
|
||||
|
||||
-- | read a CSV stream, using the first row as a header containing
|
||||
-- field labels
|
||||
labelFields :: (Monad m, Ord a) => ConduitT [a] (M.Map a a) m ()
|
||||
labelFields = await >>= \case
|
||||
Just headers -> labelLoop headers
|
||||
|
|
Loading…
Reference in New Issue
Block a user