hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Array.CSV

Contents

Description

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

Synopsis

Indexing

data Column_Ref Source

A indexed case-insensitive column references. The column following Z is AA.

Constructors

Column_Ref 

type Column_Range = (Column_Ref, Column_Ref) Source

Inclusive range of column references.

type Row_Ref = Int Source

1-indexed row reference.

row_index :: Row_Ref -> Int Source

Zero index of Row_Ref.

type Row_Range = (Row_Ref, Row_Ref) Source

Inclusive range of row references.

type Cell_Ref = (Column_Ref, Row_Ref) Source

Cell reference, column then row.

type Cell_Range = (Cell_Ref, Cell_Ref) Source

Inclusive range of cell references.

letter_index :: Char -> Int Source

Case folding letter to index function. Only valid for ASCII letters.

map letter_index ['A' .. 'Z'] == [0 .. 25]
map letter_index ['a','d' .. 'm'] == [0,3 .. 12]

index_letter :: Int -> Char Source

Inverse of letter_index.

map index_letter [0,3 .. 12] == ['A','D' .. 'M']

column_index :: Column_Ref -> Int Source

Translate column reference to 0-index.

:set -XOverloadedStrings
map column_index ["A","c","z","ac","XYZ"] == [0,2,25,28,17575]

interior_column_index :: Column_Range -> Column_Ref -> Int Source

Column reference to interior index within specified range. Type specialised index.

map (Data.Ix.index ('A','Z')) ['A','C','Z'] == [0,2,25]
map (interior_column_index ("A","Z")) ["A","C","Z"] == [0,2,25]
map (Data.Ix.index ('B','C')) ['B','C'] == [0,1]
map (interior_column_index ("B","C")) ["B","C"] == [0,1]

column_ref :: Int -> Column_Ref Source

Inverse of column_index.

let c = ["A","Z","AA","AZ","BA","BZ","CA"]
in map column_ref [0,25,26,51,52,77,78] == c
column_ref (0+25+1+25+1+25+1) == "CA"

column_ref_pred :: Column_Ref -> Column_Ref Source

Type specialised pred.

column_ref_pred "DF" == "DE"

column_ref_succ :: Column_Ref -> Column_Ref Source

Type specialised succ.

column_ref_succ "DE" == "DF"

column_indices :: Column_Range -> (Int, Int) Source

Bimap of column_index.

column_indices ("b","p") == (1,15)
column_indices ("B","IT") == (1,253)

column_range :: Column_Range -> [Column_Ref] Source

Type specialised range.

column_range ("L","R") == ["L","M","N","O","P","Q","R"]
Data.Ix.range ('L','R') == "LMNOPQR"

column_in_range :: Column_Range -> Column_Ref -> Bool Source

Type specialised inRange.

map (column_in_range ("L","R")) ["A","N","Z"] == [False,True,False]
map (column_in_range ("L","R")) ["L","N","R"] == [True,True,True]
map (Data.Ix.inRange ('L','R')) ['A','N','Z'] == [False,True,False]
map (Data.Ix.inRange ('L','R')) ['L','N','R'] == [True,True,True]

column_range_size :: Column_Range -> Int Source

Type specialised rangeSize.

map column_range_size [("A","Z"),("AA","ZZ")] == [26,26 * 26]
Data.Ix.rangeSize ('A','Z') == 26

row_range :: Row_Range -> [Row_Ref] Source

Type specialised range.

cell_ref_minima :: Cell_Ref Source

The standard uppermost leftmost cell reference, A1.

Just cell_ref_minima == parse_cell_ref "A1"

parse_cell_ref :: String -> Maybe Cell_Ref Source

Cell reference parser for standard notation of (column,row).

parse_cell_ref "CC348" == Just ("CC",348)

cell_ref_pp :: Cell_Ref -> String Source

Cell reference pretty printer.

cell_ref_pp ("CC",348) == "CC348"

cell_index :: Cell_Ref -> (Int, Int) Source

Translate cell reference to 0-indexed pair.

cell_index ("CC",348) == (80,347)
Data.Ix.index (("AA",1),("ZZ",999)) ("CC",348) == 54293

cell_range :: Cell_Range -> [Cell_Ref] Source

Type specialised range, cells are in column-order.

cell_range (("AA",1),("AC",1)) == [("AA",1),("AB",1),("AC",1)]
let r = [("AA",1),("AA",2),("AB",1),("AB",2),("AC",1),("AC",2)]
in cell_range (("AA",1),("AC",2)) == r
Data.Ix.range (('A',1),('C',1)) == [('A',1),('B',1),('C',1)]
let r = [('A',1),('A',2),('B',1),('B',2),('C',1),('C',2)]
in Data.Ix.range (('A',1),('C',2)) == r

cell_range_row_order :: Cell_Range -> [Cell_Ref] Source

Variant of cell_range in row-order.

let r = [(AA,1),(AB,1),(AC,1),(AA,2),(AB,2),(AC,2)]
in cell_range_row_order (("AA",1),("AC",2)) == r

TABLE

type CSV_Has_Header = Bool Source

When reading a CSV file is the first row a header?

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 perhaps a header.

csv_table_read :: CSV_Opt -> (String -> a) -> FilePath -> IO (CSV_Table a) Source

Read Table from CSV file.

csv_table_read' :: (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 Table.

csv_table_write :: (a -> String) -> CSV_Opt -> FilePath -> CSV_Table a -> IO () Source

Write Table to CSV file.

csv_table_write' :: (a -> String) -> CSV_Opt -> FilePath -> Table a -> IO () Source

Write Table only (no header).

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])