module Data.Riff.Parse
( withRiffFile
, parseRiffFileStream
, getRiffFile
) where
import Data.Riff.RiffData
import Data.Riff.InternalUtil
import Control.Monad (when, replicateM)
import Data.Binary.Get
import qualified Data.ByteString.Lazy as BL
import Data.Char (chr)
import Data.Word (Word8)
import GHC.IO.IOMode (IOMode(..))
import System.IO (withBinaryFile)
withRiffFile :: FilePath
-> (Either ParseError RiffFile -> IO ())
-> IO ()
withRiffFile filePath action = withBinaryFile filePath ReadMode $ \h -> do
riffData <- fmap parseRiffFileStream (BL.hGetContents h)
action riffData
parseRiffFileStream :: BL.ByteString
-> Either ParseError RiffFile
parseRiffFileStream input =
case runGetOrFail getRiffFile input of
Left (_, offset, error) -> Left (offset, error)
Right (_, _, result) -> Right result
data ParseContext = ParseContext
{ getSize :: Get RiffChunkSize
}
getRiffFile :: Get RiffFile
getRiffFile = do
id <- getIdentifier
(context, fileType) <- case id of
"RIFF" -> return (leContext, RIFF)
"RIFX" -> return (beContext, RIFX)
_ -> do
fail $ "RIFF file not allowed to start with chunk id: '" ++ id ++ "'. Must start with either RIFF or RIFX"
size <- getSize $ context
riffType <- getIdentifier
contents <- parseChunkList context (size 4)
return RiffFile
{ riffFileType = fileType
, riffFileFormatType = riffType
, riffFileChildren = contents
}
where
leContext = ParseContext getWord32le
beContext = ParseContext getWord32be
parseChunkList :: ParseContext -> RiffChunkSize -> Get [RiffChunk]
parseChunkList _ 0 = return []
parseChunkList context totalSize = do
(nextChunk, dataSize) <- getRiffChunk context
let chunkSize = 8 + padToWord dataSize
if totalSize <= chunkSize
then return [nextChunk]
else do
following <- parseChunkList context (totalSize chunkSize)
return $ nextChunk : following
getRiffChunk :: ParseContext -> Get (RiffChunk, RiffChunkSize)
getRiffChunk context = do
id <- getIdentifier
size <- getSize $ context
if id == "LIST"
then do
guardListSize id size
formType <- getIdentifier
children <- parseChunkList context (size 4)
skipToWordBoundary size
return (RiffChunkParent
{ riffFormTypeInfo = formType
, riffChunkChildren = children
}, size)
else do
riffData <- getLazyByteString (fromIntegral size)
skipToWordBoundary size
return (RiffChunkChild
{ riffChunkId = id
, riffData = riffData
}, size)
where
guardListSize id size = when (size < 4) $ do
fail $ message id size
where
message id size =
"List Chunk Id '" ++ id
++ "' had chunk size " ++ show size
++ " which is less than 4 and invalid."
skipToWordBoundary :: RiffChunkSize -> Get ()
skipToWordBoundary size = do
empty <- isEmpty
when (not empty && size `mod` 2 == 1) $ skip 1
getNWords :: Int -> Get [Word8]
getNWords n = replicateM n getWord8
getNChars :: Int -> Get String
getNChars = fmap (fmap byteToChar) . getNWords
byteToChar :: Word8 -> Char
byteToChar = chr . fromIntegral
getIdentifier = getNChars 4