Safe Haskell | None |
---|---|
Language | Haskell2010 |
DataFrame.Lazy.IO.CSV
Synopsis
- data ReadOptions = ReadOptions {}
- defaultOptions :: ReadOptions
- readCsv :: FilePath -> IO DataFrame
- readTsv :: FilePath -> IO DataFrame
- readSeparated :: Char -> ReadOptions -> FilePath -> IO (DataFrame, (Integer, Text, Int))
- getInitialDataVectors :: Int -> IOVector MutableColumn -> [Text] -> IO ()
- inferValueType :: Text -> Text
- readSingleLine :: Char -> Text -> Handle -> IO ([Text], Text)
- fillColumns :: Int -> Char -> IOVector MutableColumn -> IOVector [(Int, Text)] -> Text -> Handle -> IO (Text, Int)
- writeValue :: IOVector MutableColumn -> IOVector [(Int, Text)] -> Int -> Int -> Text -> IO ()
- freezeColumn :: IOVector MutableColumn -> Vector [(Int, Text)] -> ReadOptions -> Int -> IO Column
- parseSep :: Char -> Text -> [Text]
- record :: Char -> Parser [Text]
- parseRow :: Char -> Parser [Text]
- field :: Char -> Parser Text
- unquotedTerminators :: Char -> Set Char
- unquotedField :: Char -> Parser Text
- quotedField :: Parser Text
- lineEnd :: Parser ()
- countRows :: Char -> FilePath -> IO Int
- writeCsv :: FilePath -> DataFrame -> IO ()
- writeSeparated :: Char -> FilePath -> DataFrame -> IO ()
- getRowAsText :: DataFrame -> Int -> [Text]
Documentation
data ReadOptions Source #
Record for CSV read options.
defaultOptions :: ReadOptions Source #
By default we assume the file has a header, we infer the types on read and we convert any rows with nullish objects into Maybe (safeRead).
readCsv :: FilePath -> IO DataFrame Source #
Reads a CSV file from the given path. Note this file stores intermediate temporary files while converting the CSV from a row to a columnar format.
readTsv :: FilePath -> IO DataFrame Source #
Reads a tab separated file from the given path. Note this file stores intermediate temporary files while converting the CSV from a row to a columnar format.
readSeparated :: Char -> ReadOptions -> FilePath -> IO (DataFrame, (Integer, Text, Int)) Source #
Reads a character separated file into a dataframe using mutable vectors.
getInitialDataVectors :: Int -> IOVector MutableColumn -> [Text] -> IO () Source #
inferValueType :: Text -> Text Source #
fillColumns :: Int -> Char -> IOVector MutableColumn -> IOVector [(Int, Text)] -> Text -> Handle -> IO (Text, Int) Source #
Reads rows from the handle and stores values in mutable vectors.
writeValue :: IOVector MutableColumn -> IOVector [(Int, Text)] -> Int -> Int -> Text -> IO () Source #
Writes a value into the appropriate column, resizing the vector if necessary.
freezeColumn :: IOVector MutableColumn -> Vector [(Int, Text)] -> ReadOptions -> Int -> IO Column Source #
Freezes a mutable vector into an immutable one, trimming it to the actual row count.
quotedField :: Parser Text Source #