-- | Meapsoft analysis data input. module Sound.Analysis.Meapsoft.Data where import Data.Array.Unboxed {- array -} import qualified Data.ByteString as B {- bytestring -} import qualified Data.ByteString.Char8 as C {- bytestring -} import qualified Data.ByteString.Lazy as L {- bytestring -} import qualified Data.ByteString.Lex.Double as P {- bytestring-lexing -} import qualified Text.Delimited as D {- delimited-text -} read_inf :: Fractional n => String -> n read_inf s = case s of "Infinity" -> 1/0 "-Infinity" -> -1/0 _ -> error ("read_inf: could not read " ++ show s) to_f :: Fractional n => B.ByteString -> n to_f s = maybe (read_inf (C.unpack s)) (realToFrac . fst) (P.readDouble s) -- | Given the number of columns, reads an entire MEAPsoft data set -- into a list and returns the data paired with the number of rows. read_data :: Fractional n => FilePath -> Int -> IO (Int,[n]) 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,ds) class Floating a => Meap_Data a where meap_data_uarray :: Int -> Int -> [a] -> UArray (Int,Int) a meap_data_index :: UArray (Int,Int) a -> (Int,Int) -> a instance Meap_Data Float where meap_data_uarray nc nr ds = listArray ((0,0),(nr - 1,nc - 1)) ds meap_data_index = (!) instance Meap_Data Double where meap_data_uarray nc nr ds = listArray ((0,0),(nr - 1,nc - 1)) ds meap_data_index = (!)