| Maintainer | Baldur Blöndal <baldurpet@gmail.com> |
|---|---|
| Safe Haskell | Safe-Inferred |
Codec.ImageType
Contents
Description
Infers an image's type by looking at its initial values and comparing against some magic bytes:
>>>:set -XOverloadedStrings>>>import Codec.ImageType>>>import System.IO>>>import qualified Data.ByteString as B>>>>>>h <- openFile "/tmp/1_webp_ll.webp" ReadMode>>>bytes <- hGet h 32>>>B.isInfixOf "RIFF" bytesTrue>>>bytes"RIFF\144h\SOH\NULWEBPVP8L\131h\SOH\NUL/\143\SOHK\DLE\141\&8l\219F\146\224">>>getFileType "/tmp/1_webp_ll.webp"Just "webp"
Some other examples:
>>>import System.Process>>>import System.Directory>>>import Control.Monad>>>let findTiffs = lines <$> readProcess "locate" ["*.tiff"] "">>>length <$> findTiffs25>>>findTiffs >>= filterM doesFileExist >>= mapM getFileType[Just "tiff",Just "tiff", …>>>sequence_ <$> (findTiffs >>= filterM doesFileExist >>= mapM getFileType)Just ()
- getFileType :: FilePath -> IO (Maybe String)
- getFileTypes :: FilePath -> IO [String]
- isJpeg :: FilePath -> IO Bool
- isPng :: FilePath -> IO Bool
- isGif :: FilePath -> IO Bool
- isTiff :: FilePath -> IO Bool
- isRgb :: FilePath -> IO Bool
- isPbm :: FilePath -> IO Bool
- isPgm :: FilePath -> IO Bool
- isPpm :: FilePath -> IO Bool
- isRast :: FilePath -> IO Bool
- isXbm :: FilePath -> IO Bool
- isBmp :: FilePath -> IO Bool
- isWebp :: FilePath -> IO Bool
- isExr :: FilePath -> IO Bool
- testJpeg :: ByteString -> Maybe String
- testPng :: ByteString -> Maybe String
- testGif :: ByteString -> Maybe String
- testTiff :: ByteString -> Maybe String
- testRgb :: ByteString -> Maybe String
- testPbm :: ByteString -> Maybe String
- testPgm :: ByteString -> Maybe String
- testPpm :: ByteString -> Maybe String
- testRast :: ByteString -> Maybe String
- testXbm :: ByteString -> Maybe String
- testBmp :: ByteString -> Maybe String
- testWebp :: ByteString -> Maybe String
- testExr :: ByteString -> Maybe String
Actions
getFileType :: FilePath -> IO (Maybe String)Source
Gets a ginel possible file types based on fairly arbitrary tie breaking.
>>>import System.Directory>>>import Control.Monad>>>getDirectoryContents "." >>= filterM doesFileExist >>= mapM getFileType[Just "rast",Just "jpeg",Nothing,Just "webp",Just "gif",Just "pgm",Just "webp",Nothing,Just "webp",Just "exr"]
getFileTypes :: FilePath -> IO [String]Source
Gets possible file types. Returns empty list if nothing is found, otherwise a list of matches.
>>>import System.Directory>>>import Control.Monad>>>getDirectoryContents "." >>= filterM doesFileExist >>= mapM getFileTypes[["rast"],["jpeg"],[],["webp"],["gif"],["pgm"],["webp"],[],["webp"],["exr"]]
Predicates
isJpeg :: FilePath -> IO BoolSource
Checks if file is jpeg.
>>>import Codec.ImageType>>>import Control.Monad>>>import System.Directory>>>>>>>>>getDirectoryContents "." >>= filterM doesFileExist >>= filterM isJpeg["file2.jpeg","file1.jpeg"]
Getting file type name
testJpeg :: ByteString -> Maybe StringSource
Joint Photographic Experts Group (JPEG). Returns Just jpeg if
file satisfies check.
testPng :: ByteString -> Maybe StringSource
Portable Network Graphics (PNG). Returns Just png if file
satisfies check against magic number 89 50 4e 47 0d 0a 1a 0a.
testGif :: ByteString -> Maybe StringSource
Graphics Interchange Format (GIF). Returns Just gif if file
satisfies check against magic number GIF87a and GIF89a.
testTiff :: ByteString -> Maybe StringSource
Tagged Image File Format (TIFF). Returns Just tiff if first
short is II or MM.
testRgb :: ByteString -> Maybe StringSource
SGI image library. Checks magic number (decimal value 474 as a
short) that identifies file as an SGI image file and then returns
Just rgb.
testPbm :: ByteString -> Maybe StringSource
PBM (portable bitmap). Returns Just pbm if file satisfies check.
testPgm :: ByteString -> Maybe StringSource
PGM (portable graymap). Returns Just pgm if file satisfies check.
testPpm :: ByteString -> Maybe StringSource
PPM (portable pixmap). Returns Just ppm if file satisfies check.
testRast :: ByteString -> Maybe StringSource
Sun raster file. Returns Just rast if file satisfies check.
testXbm :: ByteString -> Maybe StringSource
X bitmap (X10 or X11). Returns Just xbm if file satisfies check.