module Sound.Analysis.Meapsoft.Data ( read_data ) where

import Data.Array.Unboxed
import qualified Data.ByteString as B
import           Data.ByteString.Char8 (unpack)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lex.Double as B
import qualified Text.Delimited as D

read_inf :: String -> Double
read_inf s = case s of
                "Infinity"  ->  1/0
                "-Infinity" -> -1/0
                _ -> error ("Could not read " ++ show s)

to_f :: B.ByteString -> Double
to_f s = maybe (read_inf (unpack s)) fst (B.readDouble s)

-- | Given the number of columns, reads an entire MEAPsoft data set
--   into an 'UArray' and returns the data paired with the number of
--   rows.
read_data :: FilePath -> Int -> IO (Int, UArray (Int, Int) Double)
read_data fn nc = do
  s <- L.readFile fn
  let (Right xs) = D.decode " \t" s
      xs' = map (take nc . drop 1) (drop 1 xs)
      nr = length xs'
      ds = map to_f (concat xs')
  return (nr, listArray ((0,0), (nr - 1, nc - 1)) ds)