Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Regular matrix array data, Csv, column & row indexing.
Synopsis
- csv_requires_quote :: String -> Bool
- csv_quote :: String -> String
- csv_quote_if_req :: String -> String
- type Csv_Has_Header = Bool
- type Csv_Delimiter = Char
- type Csv_Allow_Linebreaks = Bool
- data Csv_Align_Columns
- type Csv_Opt = (Csv_Has_Header, Csv_Delimiter, Csv_Allow_Linebreaks, Csv_Align_Columns)
- def_csv_opt :: Csv_Opt
- type Csv_Table a = (Maybe [String], Table a)
- csv_table_read :: Csv_Opt -> (String -> a) -> FilePath -> IO (Csv_Table a)
- csv_table_read_def :: (String -> a) -> FilePath -> IO (Table a)
- csv_table_read_plain :: FilePath -> IO (Table String)
- csv_table_with :: Csv_Opt -> (String -> a) -> FilePath -> (Csv_Table a -> b) -> IO b
- csv_table_align :: Csv_Align_Columns -> Table String -> Table String
- csv_table_pp :: (a -> String) -> Csv_Opt -> Csv_Table a -> String
- csv_table_write :: (a -> String) -> Csv_Opt -> FilePath -> Csv_Table a -> IO ()
- csv_table_write_def :: (a -> String) -> FilePath -> Table a -> IO ()
- csv_table_write_plain :: FilePath -> Table String -> IO ()
- table_lookup :: Table a -> (Int, Int) -> a
- table_row :: Table a -> Row_Ref -> [a]
- table_column :: Table a -> Column_Ref -> [a]
- table_column_lookup :: Eq a => Table a -> (Column_Ref, Column_Ref) -> a -> Maybe a
- table_cell :: Table a -> Cell_Ref -> a
- table_lookup_row_segment :: Table a -> (Int, (Int, Int)) -> [a]
- table_row_segment :: Table a -> (Row_Ref, Column_Range) -> [a]
- table_to_array :: Table a -> Array Cell_Ref a
- csv_array_read :: Csv_Opt -> (String -> a) -> FilePath -> IO (Array Cell_Ref a)
- csv_field_str :: CSVField -> String
- csv_error_recover :: CSVError -> CSVRow
- csv_row_recover :: Either [CSVError] CSVRow -> CSVRow
- csv_load_irregular :: (String -> a) -> FilePath -> IO [[a]]
- csv_write_irregular :: (a -> String) -> Csv_Opt -> FilePath -> Csv_Table a -> IO ()
- csv_write_irregular_def :: (a -> String) -> FilePath -> Table a -> IO ()
- type P2_Parser t1 t2 = (String -> t1, String -> t2)
- csv_table_read_p2 :: P2_Parser t1 t2 -> Csv_Opt -> FilePath -> IO (Maybe (String, String), [(t1, t2)])
- type P5_Parser t1 t2 t3 t4 t5 = (String -> t1, String -> t2, String -> t3, String -> t4, String -> t5)
- type P5_Writer t1 t2 t3 t4 t5 = (t1 -> String, t2 -> String, t3 -> String, t4 -> String, t5 -> String)
- csv_table_read_p5 :: P5_Parser t1 t2 t3 t4 t5 -> Csv_Opt -> FilePath -> IO (Maybe [String], [(t1, t2, t3, t4, t5)])
- csv_table_write_p5 :: P5_Writer t1 t2 t3 t4 t5 -> Csv_Opt -> FilePath -> (Maybe [String], [(t1, t2, t3, t4, t5)]) -> IO ()
- csv_table_read_t9 :: (String -> t) -> Csv_Opt -> FilePath -> IO (Maybe [String], [T9 t])
Field / Quote
csv_requires_quote :: String -> Bool Source #
Quoting is required is the string has a double-quote, comma newline or carriage-return.
csv_quote :: String -> String Source #
Quoting places double-quotes at the start and end and escapes double-quotes.
csv_quote_if_req :: String -> String Source #
Quote field if required.
Table
type Csv_Has_Header = Bool Source #
When reading a CSV file is the first row a header?
type Csv_Delimiter = Char Source #
Alias for Char
, allow characters other than ,
as delimiter.
type Csv_Allow_Linebreaks = Bool Source #
Alias for Bool
, allow linebreaks in fields.
data Csv_Align_Columns Source #
When writing a CSV file should the delimiters be aligned, ie. should columns be padded with spaces, and if so at which side of the data?
type Csv_Opt = (Csv_Has_Header, Csv_Delimiter, Csv_Allow_Linebreaks, Csv_Align_Columns) Source #
CSV options.
def_csv_opt :: Csv_Opt Source #
Default CSV options, no header, comma delimiter, no linebreaks, no alignment.
csv_table_read :: Csv_Opt -> (String -> a) -> FilePath -> IO (Csv_Table a) Source #
Read Csv_Table
from CSV
file.
csv_table_read_def :: (String -> a) -> FilePath -> IO (Table a) Source #
Read Table
only with def_csv_opt
.
csv_table_with :: Csv_Opt -> (String -> a) -> FilePath -> (Csv_Table a -> b) -> IO b Source #
Read and process CSV
Csv_Table
.
csv_table_align :: Csv_Align_Columns -> Table String -> Table String Source #
Align table according to Csv_Align_Columns
.
csv_table_align Csv_No_Align [["a","row","and"],["then","another","one"]]
csv_table_write_def :: (a -> String) -> FilePath -> Table a -> IO () Source #
Write Table
only (no header) with def_csv_opt
.
table_column :: Table a -> Column_Ref -> [a] Source #
Column data.
table_column_lookup :: Eq a => Table a -> (Column_Ref, Column_Ref) -> a -> Maybe a Source #
Lookup value across columns.
table_cell :: Table a -> Cell_Ref -> a Source #
Table cell lookup.
table_lookup_row_segment :: Table a -> (Int, (Int, Int)) -> [a] Source #
0
-indexed (row,column) cell lookup over column range.
table_row_segment :: Table a -> (Row_Ref, Column_Range) -> [a] Source #
Range of cells from row.
Array
table_to_array :: Table a -> Array Cell_Ref a Source #
Translate Table
to Array
. It is assumed that the Table
is
regular, ie. all rows have an equal number of columns.
let a = table_to_array [[0,1,3],[2,4,5]] in (bounds a,indices a,elems a)
> (((A,1),(C,2)) > ,[(A,1),(A,2),(B,1),(B,2),(C,1),(C,2)] > ,[0,2,1,4,3,5])
Irregular
csv_field_str :: CSVField -> String Source #
csv_error_recover :: CSVError -> CSVRow Source #
csv_load_irregular :: (String -> a) -> FilePath -> IO [[a]] Source #
Read irregular CSV
file, ie. rows may have any number of columns, including no columns.
Tuples
csv_table_read_p2 :: P2_Parser t1 t2 -> Csv_Opt -> FilePath -> IO (Maybe (String, String), [(t1, t2)]) Source #
type P5_Parser t1 t2 t3 t4 t5 = (String -> t1, String -> t2, String -> t3, String -> t4, String -> t5) Source #
type P5_Writer t1 t2 t3 t4 t5 = (t1 -> String, t2 -> String, t3 -> String, t4 -> String, t5 -> String) Source #
csv_table_read_p5 :: P5_Parser t1 t2 t3 t4 t5 -> Csv_Opt -> FilePath -> IO (Maybe [String], [(t1, t2, t3, t4, t5)]) Source #