module Sound.SDIF.Byte.Frame where
import qualified Data.ByteString.Lazy as B
import Sound.OpenSoundControl.Coding.Byte
import Sound.SDIF.Byte.Matrix
import Sound.SDIF.Type
is_frame_b :: B.ByteString -> Bool
is_frame_b frm =
let n = fromIntegral (B.length frm) 8
in frame_b_size frm == n
frame_b_type :: B.ByteString -> String
frame_b_type frm = map (toEnum . fromIntegral) (B.unpack (section frm 0 4))
frame_b_size :: B.ByteString -> Int
frame_b_size frm = decode_i32 (section frm 4 8)
frame_b_time :: B.ByteString -> Double
frame_b_time frm = decode_f32 (section frm 8 16)
frame_b_id :: B.ByteString -> Int
frame_b_id frm = decode_i32 (section frm 16 20)
frame_b_matrices :: B.ByteString -> Int
frame_b_matrices frm = decode_i32 (section frm 20 24)
frame_b_data :: B.ByteString -> B.ByteString
frame_b_data frm = section frm 24 (B.length frm)
frame_b_matrix_i :: B.ByteString -> [(Int, Int)]
frame_b_matrix_i frm =
let go i j xs =
if j == 0
then reverse xs
else let h = section' frm i (i + matrix_b_header_size)
sz = fromIntegral (matrix_b_storage_size h)
xs' = (i, i + sz) : xs
in go (i + sz) (j sz) xs'
in go 24 (fromIntegral (B.length frm) 24) []