-- | Data types for GIF images -- -- Based on the GIF87a & GIF98a specification by CompuServe Inc, 1987-1990. -- The documents can be found at -- -- - http://www.martinreddy.net/gfx/2d/GIF87a.txt -- - http://www.martinreddy.net/gfx/2d/GIF89a.txt {-# LANGUAGE DeriveFunctor #-} module GIF(module GIF,module RGB) where import RGB type File = GIF CompressedBlocks type UncompressedGIF = GIF Pixels data GIF rdata = GIF { signature::String, -- GIF87a or GIF89a screen_descriptor::ScreenDescriptor, global_color_map::Maybe ColorMap, -- if hasGlobalColorMap data_blocks::DataBlocks rdata } deriving (Show,Functor) data ScreenDescriptor = SD { swidth,sheight::Short, hasGlobalMap::Bool, colorResolution::BitCount, sortFlag::Bool, -- used in GIF89a, always False in GIF87a sbitsPerPixel::BitCount, background::Pixel, aspectRatio::Byte } -- GIF89a, always 0 in GIF87a deriving (Show) type ColorMap = [RGB Byte] type DataBlocks rdata = [DataBlock rdata] type DataBlock rdata = Either ExtensionBlock (Image rdata) data Image rdata = Image { image_descriptor::ImageDescriptor, local_colorMap::Maybe ColorMap, raster_data::rdata } deriving (Show,Functor) data ImageDescriptor = ID { left,top,iwidth,iheight::Short, hasLocalMap::Bool, interlace::Bool, ibitsPerPixel::BitCount } -- 3 bits, used only if hasLocalMap deriving (Show) {- type RasterData = Either CompressedBlocks Pixels -- GIF files always contain CompressedBlocks -} data CompressedBlocks = CB { code_size'::Int, blocks::Blocks } deriving (Show) type Blocks = [Block] type Block = [Byte] -- ^ 8 bits type Pixel = Byte type Pixels = [Pixel] -- ^ 8 bits data ExtensionBlock -- | Uninterpreted extension block = EB { function_code::Byte, -- ^ 8 bits func_data::Blocks } -- | GIF89a Graphic Control Extension (249): | GCE { disposalMethod :: Byte, -- 3 bits userInputFlag, transparentColorFlag :: Bool, delayTime :: Short, transparentColorIndex :: Byte } -- | GIF89a Comment Extension (254): | Comment String -- | GIF89a Application Extension (255): | AE { applicationIdentifier :: String, -- 8 chars applAuthenticationCode :: (Byte,Byte,Byte), applicationData :: Blocks } deriving (Show) type BitCount = Byte -- ^ 3 bits, range 1..8, stored as 0..7 in files