-- | Byte level SDIF frame data structure. module Sound.SDIF.Byte.Matrix where import qualified Data.ByteString.Lazy as B {- bytestring -} import Sound.OSC.Coding.Byte {- hosc -} import Sound.SDIF.Type -- | Data integrity check for SDIF matix byte stream. is_matrix_b :: B.ByteString -> Bool is_matrix_b mtx = let n = fromIntegral (B.length mtx) in matrix_b_storage_size mtx == n -- | Matrix header size (constant). matrix_b_header_size :: Int matrix_b_header_size = 16 -- | Extract matrix header byte stream. matrix_b_header :: B.ByteString -> B.ByteString matrix_b_header mtx = section mtx 0 (fromIntegral matrix_b_header_size) -- | Extract matrix type string. matrix_b_type :: B.ByteString -> String matrix_b_type mtx = map (toEnum . fromIntegral) (B.unpack (section mtx 0 4)) -- | Extract matrix element data 'Type'. matrix_b_data_type :: B.ByteString -> Type matrix_b_data_type mtx = decode_i32 (section mtx 4 8) -- | Extract matrix row count. matrix_b_rows :: B.ByteString -> Int matrix_b_rows mtx = decode_i32 (section mtx 8 12) -- | Extract matrix column count. matrix_b_columns :: B.ByteString -> Int matrix_b_columns mtx = decode_i32 (section mtx 12 16) -- | Extract matrix element count (ie. rows by columns). matrix_b_elements :: B.ByteString -> Int matrix_b_elements mtx = matrix_b_rows mtx * matrix_b_columns mtx -- | Calculate size of matrix data store (ie. elements by 'Type' size). matrix_b_data_size :: B.ByteString -> Int matrix_b_data_size mtx = let r = matrix_b_rows mtx c = matrix_b_columns mtx in r * c * data_type_size (matrix_b_data_type mtx) -- | Variant of 'matrix_b_data_size' taking into account required padding. matrix_b_storage_size :: B.ByteString -> Int matrix_b_storage_size mtx = let pad_bytes sz = let m = sz `mod` 8 in if m > 0 then 8 - m else 0 n = matrix_b_data_size mtx in n + pad_bytes n + 16 -- | Extract matrix data from byte stream. matrix_b_to_matrix_v :: B.ByteString -> [Datum] matrix_b_to_matrix_v mtx = let ty = matrix_b_data_type mtx sz = data_type_size ty dc = data_type_decoder ty go i j xs = if j == 0 then reverse xs else let i' = i + sz xs' = dc (section' mtx i i') : xs in go i' (j - 1) xs' in go 16 (matrix_b_elements mtx) []