hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Array.CSV

Contents

Description

Regular matrix array data, CSV, column & row indexing.

Synopsis

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?

def_csv_opt :: CSV_Opt Source #

Default CSV options, no header, comma delimiter, no linebreaks, no alignment.

type Table a = [[a]] Source #

Plain list representation of a two-dimensional table of a in row-order. Tables are regular, ie. all rows have equal numbers of columns.

type CSV_Table a = (Maybe [String], Table a) Source #

CSV table, ie. a Table with Maybe a header.

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_pp :: (a -> String) -> CSV_Opt -> CSV_Table a -> String Source #

Pretty-print CSV_Table.

csv_table_write_def :: (a -> String) -> FilePath -> Table a -> IO () Source #

Write Table only (no header) with def_csv_opt.

table_lookup :: Table a -> (Int, Int) -> a Source #

0-indexed (row,column) cell lookup.

table_row :: Table a -> Row_Ref -> [a] Source #

Row data.

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_load_irregular :: (String -> a) -> FilePath -> IO [[a]] Source #

Read irregular CSV file, ie. rows may have any number of columns, including no columns.

Tuples

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 #

csv_table_write_p5 :: P5_Writer t1 t2 t3 t4 t5 -> CSV_Opt -> FilePath -> (Maybe [String], [(t1, t2, t3, t4, t5)]) -> IO () Source #