IFF reader and writer

On AmigaOS there is a library called iffparse.library, which is used for processing the Interchange File Format, which is a binary container format developed by Electronic Arts for any kind of data. http://en.wikipedia.org/wiki/Interchange_File_Format The best known instances of this format are certainly the AIFF sampled sound format and WAV (which is RIFF, that is little endian IFF). Short question: Is there some Haskell library for parsing and constructing files of this format?

Am Freitag, 1. Dezember 2006 16:30 schrieb Henning Thielemann:
On AmigaOS there is a library called iffparse.library, which is used for processing the Interchange File Format, which is a binary container format developed by Electronic Arts for any kind of data. http://en.wikipedia.org/wiki/Interchange_File_Format The best known instances of this format are certainly the AIFF sampled sound format and WAV (which is RIFF, that is little endian IFF). Short question: Is there some Haskell library for parsing and constructing files of this format?
I don't have any Haskell lib for (R)IFF, but as one of the freealut authors I have the "pleasure" to maintain a WAV reader, among other things. IMHO WAV is one of the most idiotic, redundant and underspecified format in the world, and most existing WAV files are broken in some respect. PNGs are a bit better, but all those chunked formats are a bit problematic in practice, because new chunk types are constantly being invented, contradict other chunks, etc. etc. Quite a few concrete (R)IFF instances can contain (R)IFF within chunks themselves, furthermore you have always be prepared to handle an unknown chunk type. So a general (R)IFF type can't be much more than a tree with a tagged bunch of bytes at each node, which is not really of much help IMHO. Separate libraries for handling WAV, TIFF, PNG, AVI, etc. might make more sense, as they can reflect the underlying structure much better. Cheers, S.

On Fri, 1 Dec 2006, Sven Panne wrote:
I don't have any Haskell lib for (R)IFF, but as one of the freealut authors I have the "pleasure" to maintain a WAV reader, among other things. IMHO WAV is one of the most idiotic, redundant and underspecified format in the world, and most existing WAV files are broken in some respect. PNGs are a bit better, but all those chunked formats are a bit problematic in practice, because new chunk types are constantly being invented, contradict other chunks, etc. etc.
The idea is that unknown chunks can be ignored in most cases. Of course, this is not always possible, but there are several examples where it worked.
Quite a few concrete (R)IFF instances can contain (R)IFF within chunks themselves, furthermore you have always be prepared to handle an unknown chunk type. So a general (R)IFF type can't be much more than a tree with a tagged bunch of bytes at each node, which is not really of much help IMHO.
That's exactly what I ask for. Some of the features of the IFF like CAT and PROP chunks are rarely used, maybe because there were no libraries which support them.
Separate libraries for handling WAV, TIFF, PNG, AVI, etc. might make more sense, as they can reflect the underlying structure much better.
But they could all use a general IFF library. This way you can bundle different kinds of data in one file, say sounds and pictures for an animation.

This parser was quick to write and works on AIFF files. It does not do much validation, and bits from 2 to 4 GB in length will cause errors. module LoadIFF(IFF(..),parseIFF,IDType,FormType,ContentsType) where import Data.List(unfoldr,span) import Data.Bits((.|.),shiftL) import Data.Word(Word32) import Data.ByteString(ByteString) import qualified Data.ByteString as B(take,drop,splitAt,length,unpack) type IDType = String type FormType = String type ContentsType = String data IFF = IFF_Form {len :: Word32 ,typeID :: FormType ,parts :: [IFF] } | IFF_List {len :: Word32 ,typeID :: ContentsType ,props :: [IFF] ,parts :: [IFF] } | IFF_Cat {len :: Word32 ,typeID :: ContentsType ,parts :: [IFF] } | IFF_Prop {len :: Word32 ,typeID :: FormType ,parts :: [IFF] } | IFF_Chunk {len :: Word32 ,typeID :: IDType ,rawContent :: ByteString } instance Show IFF where show IFF_Form { typeID = name, len = size, parts = p } = "IFF_Form {typeID="++show name++",size="++show size++",parts="++show p++"}" show IFF_List { typeID = name, len = size, props = ps, parts = p } = "IFF_List {typeID="++show name++",size="++show size++",props"++show ps++",parts="++show p++"}" show IFF_Cat { typeID = name, len = size, parts = p } = "IFF_Cat {typeID="++show name++",size="++show size++",parts="++show p++"}" show IFF_Prop { typeID = name, len = size, parts = p } = "IFF_Prop {typeID="++show name++",size="++show size++",parts="++show p++"}" show IFF_Chunk { typeID = name, len = size } = "IFF_Chunk {typeID="++show name++",size="++show size++"}" b2s = map (toEnum . fromEnum) . B.unpack isProp IFF_Prop {} = True isProp _ = False parseIFF :: ByteString -> Maybe (IFF,ByteString) parseIFF b | B.length b <=8 = Nothing | otherwise = let (bID,b') = B.splitAt 4 b (bLEN,b'') = B.splitAt 4 b' (bTypeID,content) = B.splitAt 4 b'' [x1,x2,x3,x4] = map fromIntegral (B.unpack bLEN) iLEN = (shiftL x1 24) .|. (shiftL x2 16) .|. (shiftL x3 8) .|. x4 toNext = (if odd iLEN then succ else id) (fromIntegral iLEN) rest = B.drop toNext b'' in if iLEN > fromIntegral (B.length b'') then Nothing else let iff = case b2s bID of "FORM" -> IFF_Form {len = iLEN ,typeID = b2s bTypeID ,parts = unfoldr parseIFF content} "LIST" -> let (ps,cs) = span isProp (unfoldr parseIFF content) in IFF_List {len = iLEN ,typeID = b2s bTypeID ,props = ps ,parts = cs} "CAT " -> IFF_Cat {len = iLEN ,typeID = b2s bTypeID ,parts = unfoldr parseIFF content} "Prop" -> IFF_Prop {len = iLEN ,typeID = b2s bTypeID ,parts = unfoldr parseIFF content} chunkID -> IFF_Chunk {len = iLEN ,typeID = chunkID ,rawContent = content} in Just (iff,rest)

On Fri, 1 Dec 2006, Chris Kuklewicz wrote:
This parser was quick to write and works on AIFF files. It does not do much validation, and bits from 2 to 4 GB in length will cause errors.
module LoadIFF(IFF(..),parseIFF,IDType,FormType,ContentsType) where
In order to preserve your code I put it here: http://darcs.haskell.org/iff/ There was still the problem that data chunks have only an 8-byte header (chunk name and size), whereas structure chunks (FORM, CAT, LIST, PROP) contain 12 bytes (chunk name, size, format name). Some people may find the task too simple to be worth an extra library, however it would be nice if libraries that process IF formats would use a common data structure. Then it would be easy to compose IFF files from components of different type.
participants (3)
-
Chris Kuklewicz
-
Henning Thielemann
-
Sven Panne