| Copyright | (c) Martin Hoppenheit 2020-2024 | 
|---|---|
| License | MIT | 
| Maintainer | martin@hoppenheit.info | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
ExifTool
Description
This module contains bindings to the ExifTool command-line application that enable reading, writing and deleting metadata in various file formats. Here's a short code example, the details are explained below.
{-# LANGUAGE OverloadedStrings #-}
import Data.Text (Text)
import ExifTool
data Foo = Foo
  { description :: Text,
    resolution :: Int
  }
  deriving (Show)
main :: IO ()
main = withExifTool $ \et -> do
  m <- readMeta et [] "a.jpg"
  print $ Foo <$> get (Tag "Description") m <*> get (Tag "XResolution") m
  let m' = del (Tag "Description") . set (Tag "XResolution") (42 :: Int) $ m
  writeMeta et m' "a.jpg"Note that this module expects the exiftool binary to be in your PATH.
Synopsis
- data ExifTool
- startExifTool :: IO ExifTool
- stopExifTool :: ExifTool -> IO ()
- withExifTool :: (ExifTool -> IO a) -> IO a
- readMeta :: ExifTool -> [Tag] -> FilePath -> IO Metadata
- readMetaEither :: ExifTool -> [Tag] -> FilePath -> IO (Either Text Metadata)
- writeMeta :: ExifTool -> Metadata -> FilePath -> IO ()
- writeMetaEither :: ExifTool -> Metadata -> FilePath -> IO (Either Text ())
- data Metadata
- newtype Tag = Tag {}
- stripGroups :: Tag -> Tag
- data Value- = String !Text
- | Binary !ByteString
- | Number !Scientific
- | Bool !Bool
- | List ![Value]
 
- class FromValue a where
- class ToValue a where
- get :: FromValue a => Tag -> Metadata -> Maybe a
- set :: ToValue a => Tag -> a -> Metadata -> Metadata
- del :: Tag -> Metadata -> Metadata
Running an ExifTool instance
Most functions in this module interact with an ExifTool instance
 i.e., a running ExifTool process represented by the ExifTool data
 type. The easiest way to obtain an instance is the withExifTool
 function that takes care of starting and stopping the process.
An ExifTool instance, initialized with startExifTool and terminated with
 stopExifTool.
startExifTool :: IO ExifTool Source #
Start an ExifTool instance. Use stopExifTool when done, or withExifTool
 to combine both steps.
stopExifTool :: ExifTool -> IO () Source #
Stop a running ExifTool instance.
withExifTool :: (ExifTool -> IO a) -> IO a Source #
Start an ExifTool instance, do something with it, then stop it.
Reading and writing metadata
The ExifTool instance can then be used to read or write metadata in a file with the respective functions.
readMeta :: ExifTool -> [Tag] -> FilePath -> IO Metadata Source #
Read the given tags from a file. Use an empty tag list to return all metadata. Tag names are returned in "simple" form without any leading group prefixes, independent of how they are specified in the given tag list.
Since: 0.2.0.0
readMetaEither :: ExifTool -> [Tag] -> FilePath -> IO (Either Text Metadata) Source #
Like readMeta, but ExifTool errors are returned as Left values instead of
 leading to runtime errors.
Since: 0.2.0.0
writeMeta :: ExifTool -> Metadata -> FilePath -> IO () Source #
Write metadata to a file. The file is modified in place, make sure you have the necessary backups!
Since: 0.2.0.0
writeMetaEither :: ExifTool -> Metadata -> FilePath -> IO (Either Text ()) Source #
Like writeMeta, but ExifTool errors are returned as Left values instead
 of leading to runtime errors.
Since: 0.2.0.0
Metadata is represented by a set of Tag/Value pairs that can be
 queried and manipulated with the respective functions.
An ExifTool tag name like Tag Description or Tag
 "EXIF:IFD0:XResolution".
stripGroups :: Tag -> Tag Source #
Remove group prefixes from a tag name e.g., stripGroups (Tag
 "XMP:XMP-dc:Description") == Tag Description.
An ExifTool tag value, enclosed in a type wrapper. The type wrapper can
 usually be ignored when using the FromValue and ToValue instances.
Constructors
| String !Text | |
| Binary !ByteString | |
| Number !Scientific | |
| Bool !Bool | |
| List ![Value] | 
class FromValue a where Source #
Data types that a Value can be turned into.
Since: 0.2.0.0
class ToValue a where Source #
Data types that can be turned into a Value.
Since: 0.2.0.0
get :: FromValue a => Tag -> Metadata -> Maybe a Source #
Retrieve the value of a tag. Tag case is ignored i.e., get (Tag
 "Description)" m == get (Tag "description") m.
Since: 0.2.0.0