-- | SDIF (Sound Description Interchange Format) module Sound.SDIF where import qualified Data.ByteString.Lazy as B import Sound.SDIF.Byte.SDIF import Sound.SDIF.Frame import Sound.SDIF.Matrix import Sound.SDIF.Type -- | SDIF data store. data SDIF = SDIF { sdif_b :: B.ByteString , sdif_frames :: Int , sdif_frame_i :: [(Int, Int)] , sdif_frame_c :: [Frame] } deriving (Eq, Show) -- | Decode 'SDIF' data stream. -- -- > b <- B.readFile "/home/rohan/sw/hsdif/Help/crotale.sdif" -- > sdif_frames (decode_sdif b) == 2 decode_sdif :: B.ByteString -> SDIF decode_sdif sdf = let n = sdif_b_frames sdf ix = sdif_b_frame_i sdf n frm (i,j) = decode_frame (section' sdf i j) s = SDIF { sdif_b = sdf , sdif_frames = n , sdif_frame_i = ix , sdif_frame_c = map frm ix } in if is_sdif_b sdf then s else error "decode_sdif" "illegal data" -- | Read and decode 'SDIF' from named file. -- -- > s <- sdif_read_file "/home/rohan/sw/hsdif/Help/crotale.sdif" -- > sdif_frame_i s == [(0,16),(16,856)] sdif_read_file :: FilePath -> IO SDIF sdif_read_file file_name = do b <- B.readFile file_name return (decode_sdif b) -- | Extract /n/th frame data from 'SDIF'. sdif_frame_b :: SDIF -> Int -> B.ByteString sdif_frame_b sdf n = let (i,j) = sdif_frame_i sdf !! n in (section' (sdif_b sdf) i j) -- | Extract and decode /n/th frame from 'SDIF'. -- -- > frame_type (sdif_frame s 0) == "SDIF" sdif_frame :: SDIF -> Int -> Frame sdif_frame sdf n = sdif_frame_c sdf !! n -- | Extract and decode /j/th matrix from /i/th frame from 'SDIF'. -- -- > matrix_type (sdif_matrix s 1 0) == "1RES" sdif_matrix :: SDIF -> Int -> Int -> Matrix sdif_matrix sdf i = frame_matrix (sdif_frame sdf i) -- | Run 'matrix_v' on result of 'sdif_matrix'. -- -- > length (sdif_matrix_v s 1 0) == 200 sdif_matrix_v :: SDIF -> Int -> Int -> [Datum] sdif_matrix_v sdf i = matrix_v . sdif_matrix sdf i