module Music.Theory.Array.CSV where
import Data.Array
import Data.Char
import Data.Function
import Data.List
import Data.String
import qualified Text.CSV.Lazy.String as C
import qualified Music.Theory.List as T
data Column_Ref = Column_Ref {column_ref_string :: String}
instance IsString Column_Ref where fromString = Column_Ref
instance Read Column_Ref where readsPrec _ s = [(Column_Ref s,[])]
instance Show Column_Ref where show = column_ref_string
instance Eq Column_Ref where (==) = (==) `on` column_index
instance Ord Column_Ref where compare = compare `on` column_index
instance Enum Column_Ref where
fromEnum = column_index
toEnum = column_ref
instance Ix Column_Ref where
range = column_range
index = interior_column_index
inRange = column_in_range
rangeSize = column_range_size
type Column_Range = (Column_Ref,Column_Ref)
type Row_Ref = Int
row_index :: Row_Ref -> Int
row_index r = r 1
type Row_Range = (Row_Ref,Row_Ref)
type Cell_Ref = (Column_Ref,Row_Ref)
type Cell_Range = (Cell_Ref,Cell_Ref)
letter_index :: Char -> Int
letter_index c = fromEnum (toUpper c) fromEnum 'A'
index_letter :: Int -> Char
index_letter i = toEnum (i + fromEnum 'A')
column_index :: Column_Ref -> Int
column_index (Column_Ref c) =
let m = iterate (* 26) 1
i = reverse (map letter_index c)
in sum (zipWith (*) m (zipWith (+) [0..] i))
interior_column_index :: Column_Range -> Column_Ref -> Int
interior_column_index (l,r) c =
let n = column_index c
l' = column_index l
r' = column_index r
in if n > r'
then error (show ("interior_column_index",l,r,c))
else n l'
column_ref :: Int -> Column_Ref
column_ref =
let rec n = case n `quotRem` 26 of
(0,r) -> [index_letter r]
(q,r) -> index_letter (q 1) : rec r
in Column_Ref . rec
column_ref_pred :: Column_Ref -> Column_Ref
column_ref_pred = pred
column_ref_succ :: Column_Ref -> Column_Ref
column_ref_succ = succ
column_indices :: Column_Range -> (Int,Int)
column_indices =
let bimap f (i,j) = (f i,f j)
in bimap column_index
column_range :: Column_Range -> [Column_Ref]
column_range rng =
let (l,r) = column_indices rng
in map column_ref [l .. r]
column_in_range :: Column_Range -> Column_Ref -> Bool
column_in_range rng c =
let (l,r) = column_indices rng
k = column_index c
in k >= l && k <= r
column_range_size :: Column_Range -> Int
column_range_size = (+ 1) . negate . uncurry () . column_indices
row_range :: Row_Range -> [Row_Ref]
row_range = range
cell_ref_minima :: Cell_Ref
cell_ref_minima = (Column_Ref "A",1)
parse_cell_ref :: String -> Maybe Cell_Ref
parse_cell_ref s =
case span isUpper s of
([],_) -> Nothing
(c,r) -> case span isDigit r of
(n,[]) -> Just (Column_Ref c,read n)
_ -> Nothing
cell_ref_pp :: Cell_Ref -> String
cell_ref_pp (Column_Ref c,r) = c ++ show r
cell_index :: Cell_Ref -> (Int,Int)
cell_index (c,r) = (column_index c,row_index r)
cell_range :: Cell_Range -> [Cell_Ref]
cell_range ((c1,r1),(c2,r2)) =
[(c,r) |
c <- column_range (c1,c2)
,r <- row_range (r1,r2)]
cell_range_row_order :: Cell_Range -> [Cell_Ref]
cell_range_row_order ((c1,r1),(c2,r2)) =
[(c,r) |
r <- row_range (r1,r2)
,c <- column_range (c1,c2)]
type CSV_Has_Header = Bool
type CSV_Delimiter = Char
type CSV_Allow_Linebreaks = Bool
data CSV_Align_Columns = CSV_No_Align | CSV_Align_Left | CSV_Align_Right
type CSV_Opt = (CSV_Has_Header,CSV_Delimiter,CSV_Allow_Linebreaks,CSV_Align_Columns)
def_csv_opt :: CSV_Opt
def_csv_opt = (False,',',False,CSV_No_Align)
type Table a = [[a]]
type CSV_Table a = (Maybe [String],Table a)
csv_table_read :: CSV_Opt -> (String -> a) -> FilePath -> IO (CSV_Table a)
csv_table_read (hdr,delim,brk,_) f fn = do
s <- readFile fn
let t = C.csvTable (C.parseDSV brk delim s)
p = C.fromCSVTable t
(h,d) = if hdr then (Just (head p),tail p) else (Nothing,p)
return (h,map (map f) d)
csv_table_read' :: (String -> a) -> FilePath -> IO (Table a)
csv_table_read' f = fmap snd . csv_table_read def_csv_opt f
csv_table_with :: CSV_Opt -> (String -> a) -> FilePath -> (CSV_Table a -> b) -> IO b
csv_table_with opt f fn g = fmap g (csv_table_read opt f fn)
csv_table_align :: CSV_Align_Columns -> Table String -> Table String
csv_table_align align tbl =
let c = transpose tbl
n = map (maximum . map length) c
ext k s = let pd = replicate (k length s) ' '
in case align of
CSV_No_Align -> s
CSV_Align_Left -> pd ++ s
CSV_Align_Right -> s ++ pd
in transpose (zipWith (map . ext) n c)
csv_table_write :: (a -> String) -> CSV_Opt -> FilePath -> CSV_Table a -> IO ()
csv_table_write f (_,delim,brk,align) fn (hdr,tbl) = do
let tbl' = csv_table_align align (map (map f) tbl)
(_,t) = C.toCSVTable (T.mcons hdr tbl')
s = C.ppDSVTable brk delim t
writeFile fn s
csv_table_write' :: (a -> String) -> CSV_Opt -> FilePath -> Table a -> IO ()
csv_table_write' f opt fn tbl = csv_table_write f opt fn (Nothing,tbl)
table_lookup :: Table a -> (Int,Int) -> a
table_lookup t (r,c) = (t !! r) !! c
table_row :: Table a -> Row_Ref -> [a]
table_row t r = t !! row_index r
table_column :: Table a -> Column_Ref -> [a]
table_column t c = transpose t !! column_index c
table_column_lookup :: Eq a => Table a -> (Column_Ref,Column_Ref) -> a -> Maybe a
table_column_lookup t (c1,c2) e =
let a = zip (table_column t c1) (table_column t c2)
in lookup e a
table_cell :: Table a -> Cell_Ref -> a
table_cell t (c,r) =
let (r',c') = (row_index r,column_index c)
in table_lookup t (r',c')
table_lookup_row_segment :: Table a -> (Int,(Int,Int)) -> [a]
table_lookup_row_segment t (r,(c0,c1)) =
let r' = t !! r
in take (c1 c0 + 1) (drop c0 r')
table_row_segment :: Table a -> (Row_Ref,Column_Range) -> [a]
table_row_segment t (r,c) =
let (r',c') = (row_index r,column_indices c)
in table_lookup_row_segment t (r',c')
table_to_array :: Table a -> Array Cell_Ref a
table_to_array t =
let nr = length t
nc = length (t !! 0)
bnd = (cell_ref_minima,(toEnum (nc 1),nr))
asc = zip (cell_range_row_order bnd) (concat t)
in array bnd asc
csv_array_read :: CSV_Opt -> (String -> a) -> FilePath -> IO (Array Cell_Ref a)
csv_array_read opt f fn = fmap (table_to_array . snd) (csv_table_read opt f fn)