logo

Functional Specification of JPEG Decompression. and an Implementation for Free

JPEG is a standard for compressing images that has become very popular recently. Unlike general purpose compression algorithms, it exploits redundancy resulting from the two dimensional structure ture of pictures and from the continuous nature of photographic color images.
Functional Speci cation of JPEG Decompression, and an Implementation for Free Jeroen Fokker Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB Utrecht, The Netherlands [email protected], http://www.cs.ruu.nl/~jeroen August 7, 1995 Abstract A decoder for images compressed by the JPEG algorithm is stated in the pure functional programming language Gofer. The program can be regarded as a mathematical speci cation of the decompression algorithm the concise description (which is included in full) is very suitable for learning about the algorithm. At the same time the `speci cation' is an executable program, which shows the usefulness of a functional programming language as a prototyping tool for graphics algorithms. All functions are de ned as much as possible at the function level, i.e. as compositions of other functions. A tutorial on the important concept of a `State Monad', which plays an important role in the program, is included. From a functional programming theoretical point of view, the new technique of currying a state monad, which is introduced, and its application in the program, are interesting. 1 Introduction JPEG is a standard for compressing images that has become very popular recently. Unlike general purpose compression algorithms, it exploits redundancy resulting from the two-dimensional struc- ture of pictures, and from the continuous nature of photographic color images. Furthermore, it o ers the possibility to let the compression lose some information, which is intended to be hardly noticeable by the human viewer. JPEG is named after its designer, the Joint (ISO and CCITT) Photographic Expert Group. In the JPEG algorithm various techniques are combined: Hu man encoding, run-length encoding, di erential encoding, quantization, cosine transform, and data reordering. A general introduction to the algorithm is given by Wallace Wall91] in a 17 page article. It contains a numeric example which is quite instructive however the information is not intended to be detailed enough to be able to implement the algorithm. For that, you would need the o cial (draft) standard ISO93] (210 pages) and/or the book that explains it PeMi93] (334 pages). The ISO description in the standard is not so nice as Wallace's article: algorithms are given by unstructured owcharts, use fuzzy identi ers and lots of indices and pointers, and are laid out poorly. A typical example is: CODE=(SLL CODE 1)+ NEXTBIT J=VALPTR (I) J=J+CODE-MINCODE (I) I would therefore not recommend the ISO document for learning about the JPEG algorithm. In some circles, functional programming has the reputation of being an academic plaything, only useful for toy problems like ` bonacci' and `8 queens' and maybe some AI applications. This might 1 be true for the earlier functional languages, but certainly not for the modern, polymorphically typed and lazily evaluated languages like Haskell HuFa92], Gofer Jone94] and Clean PlEe95]. We will prove this by giving an implementation of a JPEG decoder in the Gofer language. This article can serve as a: Speci cation. The program has the conciseness of a mathematical description, and thus acts as a `functional speci cation'. Unlike other speci cation formalisms, the language has a well de ned semantics, and an interpreter that can check type correctness. Teaching text. The JPEG format can be understood by studying the decoder. Due to the abstraction mechanisms in the language, various aspects of the algorithm can be isolated and understood separately. Implementation. The program is executable, and has been applied successfully to decode images. The program is very slow (it takes 14 minutes to decode a 384 256 image). Running time could be improved considerably by using a compiler instead of an experimental interpreter, and by optimizing some functions (the cosine transform function in section 4.2 is a good candidate for this). We have not done so, because we consider the speci cation aspect of the program more important. Functional programming tutorial and case study. Some interesting programming techniques are used and explained. It shows that a functional language can be used for real life problems in graphics. In particular, it shows that by using a `state monad', input-consuming functions can be de ned, while keeping the bene ts of abstraction in a functional language. This article assumes no knowledge of JPEG or any of its algorithms, nor of specialized functional programming techniques. Basic knowledge of functional programming (recursion, manipulation of lists and the use of types, as described in the rst few chapters of e.g. BiWa88] or Jone94]) may be helpful. However, it even may not be necessary, because the most important notions and notations are summarized in section 2. The rest of this article is divided in two parts: sections 2{3 and sections 4{6. Sections 2{3 describe some general purpose functions, that are needed in the sequel and that happen not to be part of the standard prelude of most languages. In section 2 matrix manipulation, bit lists and binary trees are dealt with. In section 3 the notions of `state function' and `monad' are introduced, and some utilities to manipulate them. Experienced functional programmers may want to skip these sections, although they might want to take a look at the end of subsection 3.4, where the new technique of currying state functions is described. The JPEG decoding algorithm proper is dealt with in sections 4{6. In section 4 the basic algo- rithms used by JPEG are de ned: Hu man coding, the Discrete Cosine Transform (DCT), and quantization. In section 5 functions for parsing the interleaved image data, and the image header are de ned. (Subsection 5.1 is a particularly nice example of using types as a guide to design functions). Section 6 contains the main program of the JPEG decoder, which calls the parser, decodes the image, and converts it to another image format. Section 7 re ects on the program and the methodology. 2 A functional library 2.1 Auxiliary functions In the functions in this article, we will use standard functions on lists, like map, concat, zipWith and transpose. These functions are de ned in the standard prelude of most functional languages. Six functions of general nature that we need are not de ned in the Gofer prelude. They are de ned in this section, and may also serve to get used to the Gofer syntax. The result of integer divisions is truncated. We provide a version which calculates the ceiling dn=de of a division instead. In the type of the function, an arrow is written not only between the type of the parameters and the result, but also between the two parameters. The type a ! b ! c is to be 2 read as a ! (b ! c), which stresses the fact that a function may also be partially parameterized with its rst parameter only. This mechanism is known as `Currying'. ceilDiv :: Int -> Int -> Int ceilDiv n d = (n+d-1)/d Partial parametrization is also useful when de ning functions. The function multi takes an integer n and a list, and replicates each element of the list, which remains unnamed, n times. multi :: Int -> a] -> a] multi n = concat . map (copy n) The function is de ned as a functional composition (denoted by the standard operator `dot') of the map (copy n) function (which turns every element into a list of length n) and the concat function (which concatenates all lists into one big list). The function multi could also have been de ned by explicitly naming the second parameter: multi n xs = concat (map (copy n) xs). However, this is avoided whenever possible in order to not overwhelm the reader with unnecessary names. Occasionally, we will also need to compose functions of two parameters. As this is not a standard function, we will de ne it here. The function o may be used as an in x operator by writing its name in back quotes. infixr 9 `o` o :: (c->d) -> (a->b->c) -> (a->b->d) (g `o` f) x y = g (f x y) In addition, we de ne an explicit denotation ap for functional application, and a variant ap' with its parameters reversed: ap :: (a->b) -> a -> b ap f x = f x ap' :: a -> (a->b) -> b ap' x f = f x An unorthodox use of functions is their use as updatable association tables. The function subst modi es a given function with respect to one possible parameter. The predicate Eq a => in front of the type means that the function is only de ned for types a for which equality is de ned. In section 6 we will use this function for integer indexed lookup tables, for which we provide the type synonym Table here. subst :: Eq a => a -> b -> (a->b) -> (a->b) subst i e t j | i==j = e | otherwise = t j type Table a = Int -> a 2.2 Matrix manipulation Matrix manipulation is a rewarding area for functional programming, as the de nitions of most operations are short and elegant and don't need lots of indices as in many other formalisms. More important, we will need these functions in section 4 for the DCT operation, and in section 6 for color space conversion. A matrix is simply a list of lists, of which we will assume that the rows have equal length. The dimensions of a matrix can be indicated by a pair of two integers. type Dim = (Int,Int) type Mat a = a]] We provide a function matmap which applies a function to all elements of a matrix, a function matconcat which collapses a matrix of sub-matrices into one big matrix, and a function matzip which transforms a list of matrices into a matrix of lists of corresponding elements. matmap :: (a->b) -> Mat a -> Mat b matmap = map . map matconcat :: Mat (Mat a) -> Mat a 3 matconcat = concat . map (map concat . transpose) matzip :: Mat a] -> Mat a] matzip = map transpose . transpose The classic operations from linear algebra (inner product of vectors and linear transformation of a vector by a matrix) presuppose the existence of arithmetical operations on the elements, which is indicated by the Num a predicate in front of the type. inprod :: Num a => a] -> a] -> a inprod = sum `o` zipWith (*) matapply :: Num a => Mat a -> a] -> a] matapply m v = map (inprod v) m Inner product is de ned as elementwise multiplication followed by summation matrix application as calculating the inner product of a vector with all rows of the matrix. 2.3 Bit Streams Of a more mundane nature are some functions that address the individual bits in a byte, and by extension, in a string. In the same vein the function byte2nibs splits a byte in two four-bit nibbles. The standard function rem is used to calculate the remainder after division. type Bits = Bool] byte2bits :: Int -> Bits byte2bits x = zipWith (>=) (map (rem x) powers) (tail powers) where powers = 256,128,64,32,16,8,4,2,1] string2bits :: String -> Bits string2bits = concat . map (byte2bits.ord) byte2nibs :: Int -> (Int,Int) byte2nibs x = (x/16, x`rem`16) With some e ort, the rem operation could be avoided by repeated subtraction, but as our goal is a clear speci cation rather than an e cient implementation, we don't do that here. In other languages shifting and masking operators may be used. 2.4 Binary Trees Binary trees, which will be used to represent Hu man trees in section 4, are de ned by an algebraic type de nition. Information is stored in the Tips of the tree, there may be Nil ends, and in Bin branching points only two subtrees are given. data Tree a = Nil | Tip a | Bin (Tree a) (Tree a) The function map can be overloaded to also operate on trees, by making Tree an instance of Functor, the class of all types supporting the map function. instance Functor Tree where map f Nil = Nil map f (Tip a) = Tip (f a) map f (Bin x y) = Bin (map f x) (map f y) 4 3 Modelling of State 3.1 State Functions Modelling of state has long been a problem when using pure functional languages, which by their nature are side-e ect free. However, recently it has been discovered that state can be adequately dealt with using so-called `monads' Wadl92, Jone93, Jone95]. A `state function from s to r', or StFun s r for short, is a function that operates on a type s (the `state') and yields not only a value of type r (the `result'), but also a value of type s (the `updated state'). An algebraic type de nition, involving an explicit conversion ST is used rather than a type synonym de nition, as state functions are to be regarded as an abstract data type, to be manipulated only by the functions below. data StFun s r = SF (s -> (r,s)) Firstly, state functions are made an instance of Functor, where the map function applies a given function to the `result' part of a state function: instance Functor (StFun s) where map h (SF f) = SF g where g s = (h x,s') where (x,s') = f s Furthermore, state functions are made an instance of the Monad class. For this, a function result and a function bind need to be de ned that ful l certain laws. In this instance, the result function constructs a state function which delivers some result x without changing the state, and the bind function composes two state functions in an intricate way: instance Monad (StFun s) where result x = SF g where g s = (x,s) SF f `bind` sfh = SF g where g s = h s' where (x,s') = f s SF h = sfh x We will not use the bind function explicitly in the sequel. Instead we make use of a syntactic sugaring known as `monad comprehension', provided in the Gofer language Jone94], which is discussed in subsection 3.3. A state function can be applied to an initial state using the function st'apply. This yields the proper result only, and discards the nal state. st'apply :: StFun a b -> a -> b st'apply (SF f) s = x where (x,_) = f s 3.2 Primitive State Functions In the JPEG decoder, as a state we will basically use a list. We provide three primitive functions that operate on list states, from which the more involved ones can be constructed. The empty state function reports whether the list in the state is empty, and leaves the state unmodi ed. The item state function returns the rst element of the list in the state (which is assumed to be non-empty), and removes that element from the list. The peekitem state function returns the rst element without removing it from the list. empty :: StFun a] Bool empty = SF f where f ] = (True, ]) f xs = (False, xs) item :: StFun a] a 5 item = SF f where f (x:xs) = (x, xs) peekitem :: StFun a] a peekitem = SF f where f ys@(x:xs) = (x, ys) A fourth primitive function meets a more special purpose. In the JPEG format, a binary data stream is terminated by a two-byte marker consisting of an `\xFF' byte and a non-zero byte. If an `\xFF' byte occasionally occurs in a data stream, it is padded by an extra zero byte. The state function entropy below gets one segment of binary data, taking care of the padding, and leaves behind as nal state a list that begins with the terminating marker. entropy :: StFun String String entropy = SF f where f ('\xFF':'\x00':xs) = let (as,bs) = f xs in ('\xFF':as,bs) f ys@( '\xFF':_ ) = ( ],ys) f ( x:xs) = let (as,bs) = f xs in (x:as,bs) 3.3 Auxiliary State Functions The state function item gets one character from a string state, removing it from the state. The state function byte does the same, but yields its result as an integer rather than as a character. It can be de ned as map ord item (where ord is the primitive char-to-int function). Recall that map was overloaded in subsection 3.1, so that map h f applies a function h to the result part of a state function f . We write the de nition however in the form: byte :: StFun String Int byte = ord c | c m a] -> m a] list ] = result ] list (f:fs) = x:xs | xnumber of times, and thus results in a list of values. The function matrix is parameterized with two integers, and constructs a matrix-valued state function. Just a list, the functions exactly and matrix are de ned for any monad, but are used only for state functions in the sequel. You may therefore read StFun s instead of the arbitrary monad m in the de nitions below. exactly :: Monad m => Int -> m a -> m a] exactly 0 f = result ] exactly (n+1) f = x:xs | x m a -> m (Mat a) matrix (y,x) = exactly y . exactly x A combinator that is speci c for state functions that have a list as state is many, which applies a state function as many times as possible until the state has become the empty list. many :: StFun a] b -> StFun a] b] many f = if b then ] else y:ys | b (b -> StFun a (b,c)) sf'curry (SF h) = f where f b = SF g where g a = ((b',c),a') where (c,(a',b')) = h (a,b) sf'uncur :: (b -> StFun a (b,c)) -> StFun (a,b) c sf'uncur f = SF h where h (a,b) = (c, (a',b')) where SF g = f b ((b',c),a') = g a These transformations are the analogues for state functions of the curry and uncurry operations on normal functions. Note the nice symmetry in the de nitions: the equations in sf'uncur are the same as in sf'curry, written right to left. All functions de ned thus far (except entropy) are quite abstract, and should really be part of a monad or state function library. They have been treated here to make this article self-contained. The implementation of the proper JPEG algorithm starts in the next section. 4 JPEG Fundamental Algorithms 4.1 Hu man Trees A Hu man coding translates values with a higher probability of occurrence into codes of shorter length, thus reducing the overall length of a message. Hu man codes can be decoded if all possible values are stored in a binary tree. The bits in a code are used as navigating instructions in the tree on arriving in a tip, the value found there is the value corresponding to the bits consumed. As the number of bits that make up one code is variable, the decoding function is best modelled as a state function, which consumes as many bits as necessary from a Bool] (or Bits) state. 7 lookup :: Tree a -> StFun Bits a lookup (Tip x) = result x lookup (Bin lef rit) = x | b recursion when 63 values have been accumulated. A special case is when both r and s are zero, which is a signal that only zeroes should be appended to complete a batch of 63 values. acdecode :: Tree (Int,Int) -> Int -> StFun Bits Int] acdecode t k = x | (r,s) Float] idct1 = matapply cosinuses cosinuses :: Mat Float cosinuses = map f 1,3..15] where f x = map g 0..7] where g 0 = 0.5 / sqrt 2.0 g u = 0.5 * cos(fromInteger(x*u)*(pi/16.0)) In JPEG a two-dimensional version of the DCT is used, which transforms an 8 8 block of data into 8 8 DCT coe cients. A two-dimensional DCT can be performed by rst transforming each row, and then transforming each column of the resulting 8 rows of coe cients: idct2 :: Mat Float -> Mat Float idct2 = transpose . map idct1 . transpose . map idct1 In the resulting block of coe cients, the upper left value can be interpreted as the average of the original data (if you know enough of electricity this may justify the name `d(irect) c(urrent) coe cient'). The other 63 values (`ac coe cients') represent higher and higher harmonics as the bottom right is approached. The function idct1 performs 64 multiplications, and hence idct2 requires (8 + 8) 64 = 1024 multiplications. Various clever schemes, which exploit the symmetry in the cosine matrix to bring down the number of multiplications, are summarized by Pennebaker PeMi93]. Hartel and Vree HaVr92] discuss how fast algorithms for the related Fourier transform (FFT) can be implemented and optimized in a functional language. 9 4.3 Quantization and Downsampling The DCT as such does not bring in any data reduction, as an 8 8 block of image data is transformed into an 8 8 block of DCT coe cients. However, in continuous-tone images, such as scanned photographs, higher harmonics tend to be absent. Sequences of zeroes in the DCT coe cients are coded very e ciently by the run-length encoding described in subsection 4.1. To encourage the presence of zeroes, the DCT coe cients are quantized during encoding, i.e. mapped to a smaller interval, by dividing by a constant and rounding to an integer. Small coe cients will vanish, and larger coe cients lose unnecessary precision. The quantization factor can be speci ed for each coe cient separately. Thus the unimportant higher harmonics can be quantized more than the lower harmonics. The quantization factors are determined during encoding (typically by a user selecting a `quality'), and stored in the image header. During decoding, which we deal with here, the coe cients are multiplied again by the quantization factors. The coe cients in the 2-dimensional matrix of coe cients are not stored in row or column order, but in a zigzag order, which again promotes long sequences of zeroes, especially at the end if the list (bottom-right of the matrix) of coe cients. The function dequant below takes a list of 64 quantization factors and a list of 64 quantized coe cients, multiplies them together, constructs a matrix in zigzag order, and then performs a 2-dimensional inverse DCT. type QuaTab = Int] dequant ::QuaTab -> Int] -> Mat Int dequant = matmap truncate `o` idct2 `o` zigzag `o` map fromInteger `o` zipWith (*) The function zigzag puts the 64 elements of a list in the desired order in a matrix: zigzag xs = matmap (xs!!) 0, 1, 5, 6,14,15,27,28] , 2, 4, 7,13,16,26,29,42] , 3, 8,12,17,25,30,41,43] , 9,11,18,24,31,40,44,53] , 10,19,23,32,39,45,52,54] , 20,22,33,38,46,51,55,60] , 21,34,37,47,50,56,59,61] , 35,36,48,49,57,58,62,63] ] During compression, an image can optionally be `downsampled' by averaging over an (e.g. 2 2) block of pixels, and treating them as one pixel. It is common practice to decompose an image in a grey-value (`luminance') component and two components describing color information (`chromi- nance'), and downsample the chrominance information to half its resolution. This immediately alters the size of an image by a factor of 2 (two out of three components) 3 (three out of four 3 4 pixels are discarded) = 1 . During decoding the image is `upsampled' again by: 2 upsamp :: Dim -> Mat a -> Mat a upsamp (1,1) = id upsamp (x,y) = multi y . map (multi x) 5 JPEG Data Organization 5.1 Decoding Units The DCT transformation operates on an 8 8 block of integers. However, a picture is usually bigger, and consists of more components (e.g., red/green/blue or luminance/twice chrominance). In this subsection we will compose the blocks together. First, let's formalize how one 8 8 block is processed. The function dataunit is basically a state function, which consumes bits from the state and returns a DataUnit (a matrix of integers). The function is parameterized by upsampling factors, a quantization table, and two Hu man 10 trees, which are conveniently grouped together in a four-tuple called DataSpec. The function uses dcdecode to fetch a `dc' coe cient from the bits in the state. As a nal optimization this is not the value of the dc coe cient itself, but the di erence from the dc coe cient of the previous block. Therefore, the function has an additional integer parameter which speci es the previous dc coe cient, and returns the new coe cient as part of the result for use in the next block. After the dc coe cient, the ac coe cients are fetched form the bits state. Together, the coe cients are dequantized, DCTransformed and upsampled by the functions de ned in subsection 4.3. type DataUnit = Mat Int type DataSpec = (Dim, QuaTab, Tree Int, Tree (Int,Int)) dataunit :: DataSpec -> Int -> StFun Bits (Int,DataUnit) dataunit (u,q,dc,ac) x = let y=x+dx in (y, upsamp u (dequant q (y:xs))) | dx StFun (Bits,Int) DataUnit units dim = map matconcat . matrix dim . sf'uncur . dataunit A group of such big blocks, one for each image component, is called a minimum coding unit (MCU) in JPEG terminology. Imagine the case that luminance information is not downsampled, and chrominance components are downsampled by factors 2 2 and 4 4, respectively. Then we need 16 luminance units, and 4 and 1 chrominance units to make up one MCU. Indeed, the units of the various components are interleaved in this order during encoding. The development of the state function mcu, which fetches an entire MCU from a bit stream, is driven mainly by inspecting the types involved. First, we construct a version of units in which the Int is detached from the state again, and in which the Dim and DataSpec parameter are tupled together: units' :: (Dim,DataSpec) -> Int -> StFun Bits (Int,DataUnit) units' = sf'curry . uncurry units Our rst approximation of the mcu function is just applying units' to a (Dim,DataSpec) combi- nation for each component: type MCUSpec = (Dim, DataSpec)] mcu :: MCUSpec -> Int -> StFun Bits (Int,DataUnit) ] mcu = map units' The list of functions that is the result of mcu could be applied elementwise to a list of integers: mcu' :: MCUSpec -> Int] -> StFun Bits (Int,DataUnit) ] mcu' = zipWith ap . mcu A list of state functions can be transformed into a state function for a list by the list combinator from section 3.4. Then we have a state function of type StFun Bits (Int,DataUnit)]. The result part of this can be unzipped. For the functional composition, we use `o`, because mcu' has two additional parameters: 11 mcu'' :: MCUSpec -> Int] -> StFun Bits ( Int], DataUnit]) mcu'' = map unzip `o` list `o` mcu' Now we are almost done. The Int] which appears both as a parameter and as part of the result is attached to the state again, and the list of matrices in the result is matzipped to a matrix of lists: type Picture = Mat Int] mcu''' :: MCUSpec -> StFun (Bits, Int]) Picture mcu''' = map matzip . sf'uncur . mcu'' The function is now in its ideal form. The state consists of bits that contain the compressed image, and a list of integers that contains the last dc coe cient seen (one for each component). The result is a picture, which is a matrix with for each pixel information about all the components. What remains to be done is repeatedly fetch MCU's in order to make a complete picture. Note that, as it is part of the state, the list of `last dc seen' is passed silently from one MCU to the next. picture :: Dim -> MCUSpec -> StFun (Bits, Int]) Picture picture dim = map matconcat . matrix dim . mcu''' All these auxiliary functions can be summarized by the following two de nitions, which capture the entire JPEG interleaving scheme in a few lines: units dim = map matconcat . matrix dim . sf'uncur . dataunit pict dim = map matconcat . matrix dim . map matzip . sf'uncur . map unzip `o` list `o` zipWith ap . map (sf'curry . uncurry units) 5.2 JPEG Header structure What remains to be dealt with, is parsing the JPEG image header in order to collect the various Hu man tables, quantization factors and other parameters. Again, state functions facilitate things considerably. A JPEG le is partitioned in `segments'. Each segment starts with a `marker' (that indicates the type of the segment), followed by additional information. For most pictures, only four segment types are of importance: Start Of Frame (SOF), De ne Hu man Table (DHT), De ne Quantiza- tion Table (DQT), and Start Of Scan (SOS (quite appropriate)). Here are some type de nitions that describe the relevant information for each segment type. Some segments contain repeated information, for which we de ne separate types. The type XXX is for all remaining segment types, which we leave uninterpreted. type SOF = (Dim, FrameCompo]) type DHT = (Int,Int,Tree Int) type DQT = QtabCompo] type SOS = ( ScanCompo],Bits) type XXX = (Char,String) type FrameCompo = (Int,Dim,Int) type ScanCompo = (Int,Int,Int) type QtabCompo = (Int, Int]) For each type we write a state function that is able to fetch the relevant data from a string. frameCompo = (c,dim,tq) | c scanCompo = (cs,td,ta) | cs type State = (Sof,Huf,Qua,Picture) Now we call the segment function many times, providing ve functions that yield a State->State. segments :: StFun String State->State] segments = many (segment (sof,dht,dqt,sos,xxx)) where sof x s@(a,b,c,d) = (evalSOF x s, b, c, d) dht x s@(a,b,c,d) = (a, evalDHT x s, c, d) dqt x s@(a,b,c,d) = (a, b, evalDQT x s, d) sos x s@(a,b,c,d) = (a, b, c, evalSOS x s) xxx _ s = s The main decoder function applies segments as a state function to the JPEG compressed data. This yields a list of State transformations, which are applied one after another starting with an unde ned state errState. After all segments are processed, only the Picture is retained. (If you would like to inspect, say, the Hu man tables, you could use pi2 instead of pi4). jpegDecode :: String -> Picture jpegDecode = pi4 . foldl ap' errState . st'apply segments where pi4 (_,_,_,x) = x errState = (error"SOF", error"DHT", error"DQT", error"SOS") What remains to be de ned are the four eval.. . functions that interpret the segment data. They are quite boring, as they only dispatch information. The function evalSOF sets up an association table in which all frame component information is stored. The function evalDHT sorts out Hu man trees for dc and ac coe cients. The ac trees are initialized as trees of pairs instead of integers. The function evalDQT again simply sets up an association table, from which quantization tables can be fetched by identifying number. evalSOF :: SOF -> State -> Sof evalSOF (dim,xs) (~(_,sof),_,qua,_) = (dim, foldr f sof xs) where f (i,d,q) = subst i (d,qua q) evalDHT :: DHT -> State -> Huf evalDHT (0,i,tree) (_,~(hdc,hac),_,_) = (subst i tree hdc, hac) evalDHT (1,i,tree) (_,~(hdc,hac),_,_) = (hdc, subst i (map byte2nibs tree) hac) evalDQT :: DQT -> State -> Qua evalDQT xs (_,_,qua,_) = foldr f qua xs where f (i,q) = subst i q The function evalSOS sets up the MCUSpec that is needed to parameterize the function picture from section 5.1. Most important of all, the state function yielded by picture is called, using (xs, 0,0,0]) as initial state: xs is the entropy encoded data, and 0,0,0] is an initialization of the `previous dc values'. evalSOS :: SOS -> State -> Picture evalSOS (cs,xs) (((y,x),sof),(h0,h1),_,_) = st'apply thePicture (xs, 0,0,0]) where thePicture = picture mcuCount mcuSpec mcuSpec = map f cs f (id,dc,ac) = (d, (upsCount d, qt, h0 dc, h1 ac)) where (d,qt) = sof id mcuCount = ( ceilDiv y (8*maxy), ceilDiv x (8*maxx) ) upsCount (h,w) = ( maxy/h, maxx/w ) maxy = maximum ( map (fst.fst) mcuSpec ) maxx = maximum ( map (snd.fst) mcuSpec ) 6.2 Using a Picture The Picture that is the result of jpegDecode is a matrix of pixels, where each pixel consists of a list of integer components with values in the range ;128 to 127. The interpretation of the components is left unspeci ed by JPEG, but most often they represent luminance, chrominance 14 blue, and chrominance red. These values can be converted to and from the more widely used RGB coordinates by the following linear transformations: 0 1 0 10 1 0 1 0 3 6 1 10 1 1 0 5 8 R B G C = B 1 ; 1 ; 4 C B Cb C B Cb C = B ; 10 ; 10 10 C B R C @ A @ Y Y 5 A@ A @ A @ 20 20 20 A @ G A 3 6 9 3 B 1 2 0 Cr Cr 7 6 16 ; 16 ; 16 1 B A function that converts JPEG data to an RGB picture is: yCbCr2rgb = matmap f where f = map ((+128).(/15)) . matapply 15, 0, 24] , 15, -5,-12] , 15, 30, 0] ] To obtain a black-and-white picture one could set the second and third column of the matrix to zero. The resulting matrices of RGB value can be easily converted to other picture formats. For example, a conversion to `raw portable pixmap format' is done by the function ppm: ppm xss = "P6\n# Creator: Gofer JPEG decoder\n" ++ w ++ " " ++ h ++ "\n255\n" ++ (map (chr.sane) . concat . concat) xss where w = show (length (head xss)) h = show (length xss) sane x = (0 `max` x) `min` 255 A main function can be written which reads a source JPEG le and writes a destination PPM le: dst let output = (ppm . yCbCr2rgb . jpegDecode) input in writeFile dst output abort done ) This function can be applied to example lenames as follows: main = "example.ppm" article, which they inverted function by function. Their program could be extended constructing Hu man tables optimized for a particular picture. Construction of Hu man tables is actually a functional programming classic (see BiWa88]). The reader may well imagine that collecting the necessary frequency information from the image is just a matter of a few maps and concats. Finally, it would be interesting to provide the program of an interactive interface, for which functional programming techniques have become available recently (e.g. in the Clean language PlEe95]). The very e cient code produced by the Clean compiler could speed up the program dramatically, especially if the zigzag and dct functions are implemented using arrays instead of lists. We have not done so yet, because the Clean language lacks monad comprehensions, and thus would make the functions less understandable to the human reader. References BiWa88] Richard Bird and Philip Wadler. Introduction to functional programming. New York: Prentice Hall, 1988. HaVr92] Pieter Hartel and Willem Vree. `Arrays in a lazy functional language { a case study: the Fast Fourier Transform'. In: 2nd Arrays, functional languages, and parallel systems (G. Hains, ed.). Montreal: Dept. d'informatique, Universite de Montreal (publication 841), 1992, pp. 52{66. also: ftp.fwi.uva.nl/pub/computer-systems/functional/reports/ATABLE92 t.ps.Z. HuFa92] Hudak and Fasel. `A gentle introduction to Haskell'. ACM Sigplan Notices 27, 5 (may 1992), pp. T1{T53. also: haskell.cs.yale.edu/pub/haskell/tutorial. Jone93] Mark P. Jones. `A system of constructor classes: overloading and implicit higher-order polymorphism'. In: FPCA '93: Conference on Functional Pro- gramming and Computer Architecture. New York: ACM Press, 1993. also: www.cs.nott.ac.uk/Department/Sta /mpj/fpca93.html. Jone94] Mark P. Jones. Gofer 2.30 release notes. ftp.cs.nott.ac.uk/nott-fp/languages/gofer. Jone95] Mark P. Jones. `Functional programming with overloading and higher-order polymor- phism'. In: Lecture Notes of the 1st International Spring School on Advanced Functional Programming Techniques (Johan Jeuring and Erik Meijer, eds). Berlin: Springer, 1995 (LNCS 925). ISO93] International Standards Organization. Digital compression and coding of continuous- tone still images. Draft International Standard DIS 10918-1. (reprinted in PeMi93]). PeMi93] William Pennebaker and Joan Mitchell. JPEG still image data compression standard. New York: Van Nostrand Reinhold, 1993. PlEe95] Rinus Plasmeijer and Marko van Eekelen. Concurrent Clean Language Report. Nijme- gen: Dept. of Computer Science, University of Nijmegen, the Netherlands, 1995 (to appear). ftp.cs.kun.nl/pub/Clean. Wadl92] Philip Wadler. `The Essence of Functional Programming'. In: 19th Annual ACM SIG- PLAN Symposium on Principles of Programming Languages. Santa Fe, 1992 (pp. 1{14). also: ftp.dcs.glasgow.ac.uk/pub/glasgow-fp/papers/essence-of-fp.ps.Z. Wall91] Gregory Wallace. `The JPEG still picture compression standard'. Communications of the ACM 34,4, 1991 (pp. 30{44). also: ftp.uu.net/graphics/jpeg/wallace.ps.gz. 16
DMCA.com Protection Status Copyright by webtailieu.net