Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ability to work with the EXIF data contained in JPEG files.
- parseFileExif :: FilePath -> IO (Either String (Map ExifTag ExifValue))
- parseExif :: ByteString -> Either String (Map ExifTag ExifValue)
- readExifDateTime :: String -> Maybe LocalTime
- getDateTimeOriginal :: Map ExifTag ExifValue -> Maybe LocalTime
- getOrientation :: Map ExifTag ExifValue -> Maybe ImageOrientation
- data ImageOrientation
- data RotationDirection
- getGpsLatitudeLongitude :: Map ExifTag ExifValue -> Maybe (Double, Double)
- wasFlashFired :: Map ExifTag ExifValue -> Maybe Bool
- formatAsFloatingPoint :: Int -> ExifValue -> String
- getGpsDateTime :: Map ExifTag ExifValue -> Maybe LocalTime
- parseGpsTime :: ExifValue -> Maybe TimeOfDay
- data ExifValue
- = ExifNumber !Int
- | ExifText !String
- | ExifRational !Int !Int
- | ExifNumberList ![Int]
- | ExifRationalList ![(Int, Int)]
- | ExifUndefined !ByteString
- | ExifUnknown !Word16 !Int !Int
- exposureTime :: ExifTag
- fnumber :: ExifTag
- isoSpeedRatings :: ExifTag
- dateTimeOriginal :: ExifTag
- shutterSpeedValue :: ExifTag
- apertureValue :: ExifTag
- brightnessValue :: ExifTag
- exposureBiasValue :: ExifTag
- maxApertureValue :: ExifTag
- flash :: ExifTag
- focalLength :: ExifTag
- userComment :: ExifTag
- orientation :: ExifTag
- make :: ExifTag
- model :: ExifTag
- software :: ExifTag
- copyright :: ExifTag
- digitalZoomRatio :: ExifTag
- focalLengthIn35mmFilm :: ExifTag
- artist :: ExifTag
- gpsVersionID :: ExifTag
- gpsLatitudeRef :: ExifTag
- gpsLatitude :: ExifTag
- gpsLongitudeRef :: ExifTag
- gpsLongitude :: ExifTag
- gpsAltitudeRef :: ExifTag
- gpsAltitude :: ExifTag
- gpsTimeStamp :: ExifTag
- gpsSatellites :: ExifTag
- gpsStatus :: ExifTag
- gpsMeasureMode :: ExifTag
- gpsDop :: ExifTag
- gpsSpeedRef :: ExifTag
- gpsSpeed :: ExifTag
- gpsTrackRef :: ExifTag
- gpsTrack :: ExifTag
- gpsImgDirectionRef :: ExifTag
- gpsImgDirection :: ExifTag
- gpsMapDatum :: ExifTag
- gpsDestLatitudeRef :: ExifTag
- gpsDestLatitude :: ExifTag
- gpsDestLongitudeRef :: ExifTag
- gpsDestLongitude :: ExifTag
- gpsDestBearingRef :: ExifTag
- gpsDestBearing :: ExifTag
- gpsDestDistanceRef :: ExifTag
- gpsDestDistance :: ExifTag
- gpsProcessingMethod :: ExifTag
- gpsAreaInformation :: ExifTag
- gpsDateStamp :: ExifTag
- gpsDifferential :: ExifTag
- exifVersion :: ExifTag
- sensingMethod :: ExifTag
- fileSource :: ExifTag
- sceneType :: ExifTag
- makerNote :: ExifTag
- subjectDistance :: ExifTag
- meteringMode :: ExifTag
- lightSource :: ExifTag
- exifImageWidth :: ExifTag
- exifImageHeight :: ExifTag
- relatedSoundFile :: ExifTag
- focalPlaneXResolution :: ExifTag
- focalPlaneYResolution :: ExifTag
- focalPlaneResolutionUnit :: ExifTag
- dateTimeDigitized :: ExifTag
- componentConfiguration :: ExifTag
- compressedBitsPerPixel :: ExifTag
- exposureProgram :: ExifTag
- spectralSensitivity :: ExifTag
- oecf :: ExifTag
- subjectArea :: ExifTag
- subSecTime :: ExifTag
- subSecTimeOriginal :: ExifTag
- subSecTimeDigitized :: ExifTag
- flashPixVersion :: ExifTag
- colorSpace :: ExifTag
- flashEnergy :: ExifTag
- spatialFrequencyResponse :: ExifTag
- subjectLocation :: ExifTag
- exposureIndex :: ExifTag
- cfaPattern :: ExifTag
- customRendered :: ExifTag
- exposureMode :: ExifTag
- whiteBalance :: ExifTag
- sceneCaptureType :: ExifTag
- gainControl :: ExifTag
- contrast :: ExifTag
- saturation :: ExifTag
- sharpness :: ExifTag
- deviceSettingDescription :: ExifTag
- subjectDistanceRange :: ExifTag
- imageUniqueId :: ExifTag
- exifInteroperabilityOffset :: ExifTag
- imageDescription :: ExifTag
- xResolution :: ExifTag
- yResolution :: ExifTag
- resolutionUnit :: ExifTag
- dateTime :: ExifTag
- whitePoint :: ExifTag
- primaryChromaticities :: ExifTag
- yCbCrPositioning :: ExifTag
- yCbCrCoefficients :: ExifTag
- referenceBlackWhite :: ExifTag
- exifIfdOffset :: ExifTag
- printImageMatching :: ExifTag
- gpsTagOffset :: ExifTag
- data ExifTag = ExifTag {
- tagLocation :: TagLocation
- tagDesc :: Maybe String
- tagKey :: Word16
- prettyPrinter :: ExifValue -> Text
- data TagLocation
- = ExifSubIFD
- | IFD0
- | GpsSubIFD
Documentation
EXIF parsing from JPEG files.
EXIF tags are enumerated as ExifTag values, check exposureTime
for instance.
If you use the predefined ExifTag values, you don't care about details
of the ExifTag type, however you should check out the ExifValue
type.
Regarding the ExifTag type there is however a field of that type that may
interest you: prettyPrinter
. It's a function that'll format nicely an exif value
for that exif tag as a String.
For instance for the flash
ExifTag, it'll say whether the flash was
fired or not, if there was return light and so on.
Generally speaking, you start from a JPEG file, you can parse its exif tags as a Map
of
ExifTag
to ExifValue
using parseExif
or parseFileExif
.
You can enumerate the map or lookup
the tags that interest you.
There are also a couple of higher-level helpers like getOrientation
,
getDateTimeOriginal
, wasFlashFired
and getGpsLatitudeLongitude
.
When building on Windows if you have trouble with the iconv
library,
you may build without that dependency: cabal install -f-iconv
.
That way you loose nice decoding of the EXIF User Comment though.
Main functions
parseFileExif :: FilePath -> IO (Either String (Map ExifTag ExifValue)) Source
Read EXIF data from the file you give. It's a key-value map.
parseExif :: ByteString -> Either String (Map ExifTag ExifValue) Source
Read EXIF data from a lazy bytestring.
Higher-level helper functions
readExifDateTime :: String -> Maybe LocalTime Source
Decode an EXIF date time value.
Will return Nothing
in case parsing fails.
getDateTimeOriginal :: Map ExifTag ExifValue -> Maybe LocalTime Source
Extract the date and time when the picture was taken from the EXIF information.
getOrientation :: Map ExifTag ExifValue -> Maybe ImageOrientation Source
Extract the image orientation from the EXIF information.
Will return Nothing
on parse error.
data ImageOrientation Source
data RotationDirection Source
getGpsLatitudeLongitude :: Map ExifTag ExifValue -> Maybe (Double, Double) Source
Extract the GPS latitude and longitude where the picture was taken (if it is present in the EXIF)
wasFlashFired :: Map ExifTag ExifValue -> Maybe Bool Source
Will return Just True if the flash was fired, Just False if it was not, and Nothing if the file does not contain the information.
formatAsFloatingPoint :: Int -> ExifValue -> String Source
Format the exif value as floating-point if it makes sense,
otherwise use the default show
implementation.
The first parameter lets you specify how many digits after
the comma to format in the result string.
The special behaviour applies only for ExifRational
and ExifRationalList
.
getGpsDateTime :: Map ExifTag ExifValue -> Maybe LocalTime Source
Extract the GPS date time, if present in the picture.
parseGpsTime :: ExifValue -> Maybe TimeOfDay Source
read the GPS time from the gpsTimeStamp
field.
The ExifValue type
An exif value.
If you want a string describing the contents
of the value, simply use show
.
ExifNumber !Int | An exif number. Originally it could have been short, int, signed or not. |
ExifText !String | ASCII text. |
ExifRational !Int !Int | A rational number (numerator, denominator).
Sometimes we're used to it as rational (exposition time: 1/160),
sometimes as float (exposure compensation, we rather think -0.75)
|
ExifNumberList ![Int] | List of numbers. Originally they could have been short, int, signed or not. |
ExifRationalList ![(Int, Int)] | A list of rational numbers (numerator, denominator).
Sometimes we're used to it as rational (exposition time: 1/160),
sometimes as float (exposure compensation, we rather think -0.75)
|
ExifUndefined !ByteString | The undefined type in EXIF means that the contents are not specified and up to the manufacturer. In effect it's exactly a bytestring. Sometimes it's text with ASCII or UNICODE at the beginning, often it's binary in nature. |
ExifUnknown !Word16 !Int !Int | Unknown exif value type. All EXIF 2.3 types are supported, it could be a newer file. The parameters are type, count then value |
Most useful exif tags
GPS related exif tags
Less useful exif tags
If you need to declare your own exif tags
An exif tag. Normally you don't need to fiddle with this,
except maybe if the library doesn't know the particular
exif tag you're interested in.
Rather check the list of supported exif tags, like
exposureTime
and so on.
ExifTag | |
|
data TagLocation Source
Location of the tag in the JPG file structure.
Normally you don't need to fiddle with this,
except maybe if the library doesn't know the particular
exif tag you're interested in.
Rather check the list of supported exif tags, like
exposureTime
and so on.