-- | Byte level SDIF data structure. module Sound.SDIF.Byte.SDIF where import qualified Data.ByteString.Lazy as B {- bytestring -} import Sound.OSC.Coding.Byte {- hosc -} import Sound.SDIF.Type -- | Check signature of SDIF byte stream. is_sdif_b :: B.ByteString -> Bool is_sdif_b sdf = let sig = map (fromIntegral . fromEnum) "SDIF" in B.unpack (section sdf 0 4) == sig -- | Count number of frames at SDIF byte stream. sdif_b_frames :: B.ByteString -> Int sdif_b_frames sdf = let go i j n = if j == 0 then n else let sz = decode_i32 (section' sdf (i + 4) (i + 8)) + 8 in go (i + sz) (j - sz) (n + 1) in go 0 (fromIntegral (B.length sdf)) 0 -- | Extract start and end indices for /n/ frames at SDIF byte stream. sdif_b_frame_i :: B.ByteString -> Int -> [(Int, Int)] sdif_b_frame_i sdf frame_count = let go i j xs n = if n == frame_count then reverse xs else let sz = decode_i32 (section' sdf (i + 4) (i + 8)) + 8 xs' = (i, i + sz) : xs in go (i + sz) (j - sz) xs' (n + 1) in go 0 (fromIntegral (B.length sdf)) [] 0