-- | SDIF frame functions module Sound.SDIF.Frame where import qualified Data.ByteString.Lazy as B {- bytestring -} import Sound.SDIF.Byte.Frame import Sound.SDIF.Matrix import Sound.SDIF.Type -- | SDIF frame data store data Frame = Frame { frame_b :: B.ByteString , frame_type :: String , frame_size :: Int , frame_time :: Float , frame_id :: Int , frame_matrices :: Int , frame_matrix_i :: [(Int, Int)] , frame_matrix_c :: [Matrix] } deriving (Eq, Show) -- | Decode SDIF 'Frame'. decode_frame :: B.ByteString -> Frame decode_frame frm = let ty = frame_b_type frm sz = frame_b_size frm mtx (i,j) = decode_matrix (section' frm i j) ix = frame_b_matrix_i frm f = if ty == "SDIF" then Frame frm ty sz 0 0 0 [] [] else Frame { frame_b = frm , frame_type = ty , frame_size = sz , frame_time = frame_b_time frm , frame_id = frame_b_id frm , frame_matrices = frame_b_matrices frm , frame_matrix_i = ix , frame_matrix_c = map mtx ix } in if is_frame_b frm then f else error "decode_frame" "illegal data" -- | Extract /n/th matrix of 'Frame'. frame_matrix_b :: Frame -> Int -> B.ByteString frame_matrix_b frm n = let (i,j) = frame_matrix_i frm !! n in section' (frame_b frm) i j -- | Extract and decode /n/th matrix of 'Frame'. frame_matrix :: Frame -> Int -> Matrix frame_matrix frm n = frame_matrix_c frm !! n