| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DataFrame.IO.CSV
Synopsis
- data GrowingVector a = GrowingVector {}
- data GrowingUnboxedVector a = GrowingUnboxedVector {}
- data GrowingColumn
- = GrowingInt !(GrowingUnboxedVector Int) !(IORef [Int])
- | GrowingDouble !(GrowingUnboxedVector Double) !(IORef [Int])
- | GrowingText !(GrowingVector Text) !(IORef [Int])
- data HeaderSpec
- = NoHeader
- | UseFirstRow
- | ProvideNames [Text]
- data TypeSpec
- shouldInferFromSample :: TypeSpec -> Bool
- typeInferenceSampleSize :: TypeSpec -> Int
- data ReadOptions = ReadOptions {
- headerSpec :: HeaderSpec
- typeSpec :: TypeSpec
- safeRead :: Bool
- chunkSize :: Int
- dateFormat :: String
- defaultReadOptions :: ReadOptions
- newGrowingVector :: Int -> IO (GrowingVector a)
- newGrowingUnboxedVector :: Unbox a => Int -> IO (GrowingUnboxedVector a)
- appendGrowingVector :: GrowingVector a -> a -> IO ()
- appendGrowingUnboxedVector :: Unbox a => GrowingUnboxedVector a -> a -> IO ()
- freezeGrowingVector :: GrowingVector a -> IO (Vector a)
- freezeGrowingUnboxedVector :: Unbox a => GrowingUnboxedVector a -> IO (Vector a)
- readCsv :: FilePath -> IO DataFrame
- readCsvWithOpts :: ReadOptions -> FilePath -> IO DataFrame
- readTsv :: FilePath -> IO DataFrame
- readSeparated :: Char -> ReadOptions -> FilePath -> IO DataFrame
- initializeColumns :: [ByteString] -> ReadOptions -> IO [GrowingColumn]
- data InferredType
- inferType :: Text -> InferredType
- processRow :: Int -> [ByteString] -> [GrowingColumn] -> IO ()
- isNull :: Text -> Bool
- processFile :: Handle -> Char -> [GrowingColumn] -> Int -> Int -> IO ()
- parseLine :: Char -> ByteString -> [ByteString]
- parseRow :: Char -> Parser [ByteString]
- record :: Char -> Parser [ByteString]
- field :: Char -> Parser ByteString
- unquotedField :: Char -> Parser ByteString
- quotedField :: Parser ByteString
- endOfLine :: Parser ()
- freezeGrowingColumn :: GrowingColumn -> IO Column
- writeCsv :: FilePath -> DataFrame -> IO ()
- writeSeparated :: Char -> FilePath -> DataFrame -> IO ()
- getRowAsText :: DataFrame -> Int -> [Text]
Documentation
data GrowingVector a Source #
Constructors
| GrowingVector | |
data GrowingUnboxedVector a Source #
Constructors
| GrowingUnboxedVector | |
data GrowingColumn Source #
Constructors
| GrowingInt !(GrowingUnboxedVector Int) !(IORef [Int]) | |
| GrowingDouble !(GrowingUnboxedVector Double) !(IORef [Int]) | |
| GrowingText !(GrowingVector Text) !(IORef [Int]) |
data HeaderSpec Source #
Constructors
| NoHeader | File has no header row |
| UseFirstRow | Use first row as column names |
| ProvideNames [Text] | Supply names for a no-header file |
Instances
| Show HeaderSpec Source # | |
Defined in DataFrame.IO.CSV Methods showsPrec :: Int -> HeaderSpec -> ShowS # show :: HeaderSpec -> String # showList :: [HeaderSpec] -> ShowS # | |
| Eq HeaderSpec Source # | |
Defined in DataFrame.IO.CSV | |
Constructors
| InferFromSample Int | |
| SpecifyTypes [SchemaType] | |
| NoInference |
shouldInferFromSample :: TypeSpec -> Bool Source #
data ReadOptions Source #
CSV read parameters.
Constructors
| ReadOptions | |
Fields
| |
newGrowingVector :: Int -> IO (GrowingVector a) Source #
newGrowingUnboxedVector :: Unbox a => Int -> IO (GrowingUnboxedVector a) Source #
appendGrowingVector :: GrowingVector a -> a -> IO () Source #
appendGrowingUnboxedVector :: Unbox a => GrowingUnboxedVector a -> a -> IO () Source #
freezeGrowingVector :: GrowingVector a -> IO (Vector a) Source #
freezeGrowingUnboxedVector :: Unbox a => GrowingUnboxedVector a -> IO (Vector a) Source #
readCsv :: FilePath -> IO DataFrame Source #
Read CSV file from path and load it into a dataframe.
Example
ghci> D.readCsv "./data/taxi.csv"
readCsvWithOpts :: ReadOptions -> FilePath -> IO DataFrame Source #
Read CSV file from path and load it into a dataframe.
Example
ghci> D.readCsvWithOpts "./data/taxi.csv" (D.defaultReadOptions { dateFormat = "%d%-m%-Y" })
readTsv :: FilePath -> IO DataFrame Source #
Read TSV (tab separated) file from path and load it into a dataframe.
Example
ghci> D.readTsv "./data/taxi.tsv"
readSeparated :: Char -> ReadOptions -> FilePath -> IO DataFrame Source #
Read text file with specified delimiter into a dataframe.
Example
ghci> D.readSeparated ';' D.defaultReadOptions "./data/taxi.txt"
initializeColumns :: [ByteString] -> ReadOptions -> IO [GrowingColumn] Source #
data InferredType Source #
Constructors
| IntType | |
| DoubleType | |
| TextType |
inferType :: Text -> InferredType Source #
processRow :: Int -> [ByteString] -> [GrowingColumn] -> IO () Source #
processFile :: Handle -> Char -> [GrowingColumn] -> Int -> Int -> IO () Source #
parseLine :: Char -> ByteString -> [ByteString] Source #
unquotedField :: Char -> Parser ByteString Source #